| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Text.Pandoc.Z.Definition
Documentation
Instances
| Data Pandoc Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pandoc -> c Pandoc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pandoc # toConstr :: Pandoc -> Constr # dataTypeOf :: Pandoc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pandoc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pandoc) # gmapT :: (forall b. Data b => b -> b) -> Pandoc -> Pandoc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r # gmapQ :: (forall d. Data d => d -> u) -> Pandoc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pandoc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pandoc -> m Pandoc #  | |
| Monoid Pandoc Source # | |
| Semigroup Pandoc Source # | |
| Generic Pandoc Source # | |
| Read Pandoc Source # | |
| Show Pandoc Source # | |
| Eq Pandoc Source # | |
| Ord Pandoc Source # | |
| AsPandoc Pandoc Source # | |
| HasBlocks Pandoc Source # | |
| HasMeta Pandoc Source # | |
| HasPandoc Pandoc Source # | |
| Walkable Pandoc Pandoc Source # | |
| type Rep Pandoc Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Pandoc = D1 ('MetaData "Pandoc" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Pandoc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Meta) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block])))  | |
Constructors
| AlignLeft | |
| AlignRight | |
| AlignCenter | |
| AlignDefault | 
Instances
| Data Alignment Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alignment -> c Alignment # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Alignment # toConstr :: Alignment -> Constr # dataTypeOf :: Alignment -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Alignment) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment) # gmapT :: (forall b. Data b => b -> b) -> Alignment -> Alignment # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r # gmapQ :: (forall d. Data d => d -> u) -> Alignment -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alignment -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment #  | |
| Monoid Alignment Source # | |
| Semigroup Alignment Source # | |
| Generic Alignment Source # | |
| Read Alignment Source # | |
| Show Alignment Source # | |
| Eq Alignment Source # | |
| Ord Alignment Source # | |
| AsAlignment Alignment Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| HasAlignment Alignment Source # | |
| Walkable Alignment Alignment Source # | |
Defined in Text.Pandoc.Z.Definition Methods walk :: (Alignment0 -> Alignment0) -> Alignment -> Alignment # walkM :: (Monad m, Applicative m, Functor m) => (Alignment0 -> m Alignment0) -> Alignment -> m Alignment # query :: Monoid c => (Alignment0 -> c) -> Alignment -> c #  | |
| type Rep Alignment Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Alignment = D1 ('MetaData "Alignment" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) ((C1 ('MetaCons "AlignLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlignRight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AlignCenter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlignDefault" 'PrefixI 'False) (U1 :: Type -> Type)))  | |
class HasAlignment a where Source #
Instances
class AsAlignment a where Source #
Minimal complete definition
Methods
_Alignment :: Prism' a Alignment Source #
_AlignLeft :: Prism' a () Source #
_AlignRight :: Prism' a () Source #
_AlignCenter :: Prism' a () Source #
_AlignDefault :: Prism' a () Source #
Instances
| AsAlignment Alignment Source # | |
Defined in Text.Pandoc.Z.Definition Methods _Alignment :: Prism' Alignment Alignment0 Source # _AlignLeft :: Prism' Alignment () Source # _AlignRight :: Prism' Alignment () Source # _AlignCenter :: Prism' Alignment () Source # _AlignDefault :: Prism' Alignment () Source #  | |
| AsAlignment Alignment Source # | |
Defined in Text.Pandoc.Z.Definition  | |
Instances
| Data Attr Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Attr -> c Attr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Attr # dataTypeOf :: Attr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Attr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attr) # gmapT :: (forall b. Data b => b -> b) -> Attr -> Attr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r # gmapQ :: (forall d. Data d => d -> u) -> Attr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Attr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Attr -> m Attr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Attr -> m Attr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Attr -> m Attr #  | |
| Monoid Attr Source # | |
| Semigroup Attr Source # | |
| Generic Attr Source # | |
| Read Attr Source # | |
| Show Attr Source # | |
| Eq Attr Source # | |
| Ord Attr Source # | |
| AsAttr Attr Source # | |
| HasAttr Attr Source # | |
| Walkable Attr Attr Source # | |
| type Rep Attr Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Attr = D1 ('MetaData "Attr" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Attr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, Text)]))))  | |
class HasAttr a where Source #
Minimal complete definition
Instances
Constructors
| Caption (Maybe ShortCaption) [Block] | 
Instances
class HasCaption a where Source #
Minimal complete definition
Methods
caption :: Lens' a Caption Source #
maybeShortCaption :: Lens' a (Maybe ShortCaption) Source #
Instances
| HasCaption Caption Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| HasCaption Caption Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| HasCaption Figure Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| HasCaption Table Source # | |
Defined in Text.Pandoc.Z.Definition  | |
data CitationMode Source #
Constructors
| AuthorInText | |
| SuppressAuthor | |
| NormalCitation | 
Instances
class HasCitationMode a where Source #
Methods
citationMode :: Lens' a CitationMode Source #
Instances
| HasCitationMode CitationMode Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
| HasCitationMode Citation Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
| HasCitationMode CitationMode Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
class AsCitationMode a where Source #
Minimal complete definition
Methods
_CitationMode :: Prism' a CitationMode Source #
_AuthorInText :: Prism' a () Source #
_SuppressAuthor :: Prism' a () Source #
_NormalCitation :: Prism' a () Source #
Instances
| AsCitationMode CitationMode Source # | |
Defined in Text.Pandoc.Z.Definition Methods _CitationMode :: Prism' CitationMode CitationMode0 Source # _AuthorInText :: Prism' CitationMode () Source # _SuppressAuthor :: Prism' CitationMode () Source # _NormalCitation :: Prism' CitationMode () Source #  | |
| AsCitationMode CitationMode Source # | |
Defined in Text.Pandoc.Z.Definition Methods _CitationMode :: Prism' CitationMode CitationMode Source # _AuthorInText :: Prism' CitationMode () Source # _SuppressAuthor :: Prism' CitationMode () Source # _NormalCitation :: Prism' CitationMode () Source #  | |
Instances
class HasColSpec a where Source #
Constructors
| ColWidth Double | |
| ColWidthDefault | 
Instances
| Data ColWidth Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColWidth -> c ColWidth # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColWidth # toConstr :: ColWidth -> Constr # dataTypeOf :: ColWidth -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColWidth) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColWidth) # gmapT :: (forall b. Data b => b -> b) -> ColWidth -> ColWidth # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColWidth -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColWidth -> r # gmapQ :: (forall d. Data d => d -> u) -> ColWidth -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ColWidth -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColWidth -> m ColWidth #  | |
| Monoid ColWidth Source # | |
| Semigroup ColWidth Source # | |
| Generic ColWidth Source # | |
| Read ColWidth Source # | |
| Show ColWidth Source # | |
| Eq ColWidth Source # | |
| Ord ColWidth Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| AsColWidth ColWidth Source # | |
| HasColWidth ColWidth Source # | |
| Walkable ColWidth ColWidth Source # | |
| type Rep ColWidth Source # | |
Defined in Text.Pandoc.Z.Definition type Rep ColWidth = D1 ('MetaData "ColWidth" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "ColWidth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "ColWidthDefault" 'PrefixI 'False) (U1 :: Type -> Type))  | |
class HasColWidth a where Source #
Instances
class AsColWidth a where Source #
Minimal complete definition
Methods
_ColWidth :: Prism' a ColWidth Source #
_ColWidth' :: Prism' a Double Source #
_ColWidthDefault :: Prism' a () Source #
Instances
Instances
| Data Format Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Format -> c Format # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Format # toConstr :: Format -> Constr # dataTypeOf :: Format -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Format) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Format) # gmapT :: (forall b. Data b => b -> b) -> Format -> Format # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r # gmapQ :: (forall d. Data d => d -> u) -> Format -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Format -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Format -> m Format # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Format -> m Format # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Format -> m Format #  | |
| Generic Format Source # | |
| Read Format Source # | |
| Show Format Source # | |
| Eq Format Source # | |
| Ord Format Source # | |
| Wrapped Format Source # | |
| AsFormat Format Source # | |
| HasFormat Format Source # | |
| Format ~ t => Rewrapped Format t Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| Walkable Format Format Source # | |
| type Rep Format Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| type Unwrapped Format Source # | |
Defined in Text.Pandoc.Z.Definition  | |
data ListAttributes Source #
Constructors
| ListAttributes Int ListNumberStyle ListNumberDelim | 
Instances
class HasListAttributes a where Source #
Minimal complete definition
Instances
| HasListAttributes ListAttributes Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| HasListAttributes ListAttributes Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| HasListAttributes OrderedList Source # | |
Defined in Text.Pandoc.Z.Definition  | |
class AsListAttributes a where Source #
Methods
Instances
| AsListAttributes ListAttributes Source # | |
Defined in Text.Pandoc.Z.Definition Methods _ListAttributes :: Prism' ListAttributes ListAttributes0 Source #  | |
| AsListAttributes ListAttributes Source # | |
Defined in Text.Pandoc.Z.Definition Methods _ListAttributes :: Prism' ListAttributes ListAttributes Source #  | |
data ListNumberDelim Source #
Constructors
| DefaultDelim | |
| Period | |
| OneParen | |
| TwoParens | 
Instances
class HasListNumberDelim a where Source #
Methods
Instances
| HasListNumberDelim ListNumberDelim Source # | |
Defined in Text.Pandoc.Z.Definition Methods listNumberDelim :: Lens' ListNumberDelim ListNumberDelim0 Source #  | |
| HasListNumberDelim ListAttributes Source # | |
Defined in Text.Pandoc.Z.Definition Methods listNumberDelim :: Lens' ListAttributes ListNumberDelim Source #  | |
| HasListNumberDelim ListNumberDelim Source # | |
Defined in Text.Pandoc.Z.Definition Methods listNumberDelim :: Lens' ListNumberDelim ListNumberDelim Source #  | |
class AsListNumberDelim a where Source #
Minimal complete definition
Methods
_ListNumberDelim :: Prism' a ListNumberDelim Source #
_DefaultDelim :: Prism' a () Source #
_Period :: Prism' a () Source #
_OneParen :: Prism' a () Source #
_TwoParens :: Prism' a () Source #
Instances
| AsListNumberDelim ListNumberDelim Source # | |
Defined in Text.Pandoc.Z.Definition Methods _ListNumberDelim :: Prism' ListNumberDelim ListNumberDelim0 Source # _DefaultDelim :: Prism' ListNumberDelim () Source # _Period :: Prism' ListNumberDelim () Source # _OneParen :: Prism' ListNumberDelim () Source # _TwoParens :: Prism' ListNumberDelim () Source #  | |
| AsListNumberDelim ListNumberDelim Source # | |
Defined in Text.Pandoc.Z.Definition Methods _ListNumberDelim :: Prism' ListNumberDelim ListNumberDelim Source # _DefaultDelim :: Prism' ListNumberDelim () Source # _Period :: Prism' ListNumberDelim () Source # _OneParen :: Prism' ListNumberDelim () Source # _TwoParens :: Prism' ListNumberDelim () Source #  | |
data ListNumberStyle Source #
Constructors
| DefaultStyle | |
| Example | |
| Decimal | |
| LowerRoman | |
| UpperRoman | |
| LowerAlpha | |
| UpperAlpha | 
Instances
class HasListNumberStyle a where Source #
Methods
Instances
| HasListNumberStyle ListNumberStyle Source # | |
Defined in Text.Pandoc.Z.Definition Methods listNumberStyle :: Lens' ListNumberStyle ListNumberStyle0 Source #  | |
| HasListNumberStyle ListAttributes Source # | |
Defined in Text.Pandoc.Z.Definition Methods listNumberStyle :: Lens' ListAttributes ListNumberStyle Source #  | |
| HasListNumberStyle ListNumberStyle Source # | |
Defined in Text.Pandoc.Z.Definition Methods listNumberStyle :: Lens' ListNumberStyle ListNumberStyle Source #  | |
class AsListNumberStyle a where Source #
Minimal complete definition
Methods
_ListNumberStyle :: Prism' a ListNumberStyle Source #
_DefaultStyle :: Prism' a () Source #
_Example :: Prism' a () Source #
_Decimal :: Prism' a () Source #
_LowerRoman :: Prism' a () Source #
_UpperRoman :: Prism' a () Source #
_LowerAlpha :: Prism' a () Source #
_UpperAlpha :: Prism' a () Source #
Instances
| AsListNumberStyle ListNumberStyle Source # | |
Defined in Text.Pandoc.Z.Definition Methods _ListNumberStyle :: Prism' ListNumberStyle ListNumberStyle0 Source # _DefaultStyle :: Prism' ListNumberStyle () Source # _Example :: Prism' ListNumberStyle () Source # _Decimal :: Prism' ListNumberStyle () Source # _LowerRoman :: Prism' ListNumberStyle () Source # _UpperRoman :: Prism' ListNumberStyle () Source # _LowerAlpha :: Prism' ListNumberStyle () Source # _UpperAlpha :: Prism' ListNumberStyle () Source #  | |
| AsListNumberStyle ListNumberStyle Source # | |
Defined in Text.Pandoc.Z.Definition Methods _ListNumberStyle :: Prism' ListNumberStyle ListNumberStyle Source # _DefaultStyle :: Prism' ListNumberStyle () Source # _Example :: Prism' ListNumberStyle () Source # _Decimal :: Prism' ListNumberStyle () Source # _LowerRoman :: Prism' ListNumberStyle () Source # _UpperRoman :: Prism' ListNumberStyle () Source # _LowerAlpha :: Prism' ListNumberStyle () Source # _UpperAlpha :: Prism' ListNumberStyle () Source #  | |
Instances
| Data RowSpan Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowSpan -> c RowSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowSpan # toConstr :: RowSpan -> Constr # dataTypeOf :: RowSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RowSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowSpan) # gmapT :: (forall b. Data b => b -> b) -> RowSpan -> RowSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> RowSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RowSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RowSpan -> m RowSpan #  | |
| Monoid RowSpan Source # | |
| Semigroup RowSpan Source # | |
| Generic RowSpan Source # | |
| Num RowSpan Source # | |
| Read RowSpan Source # | |
| Show RowSpan Source # | |
| Eq RowSpan Source # | |
| Ord RowSpan Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| Wrapped RowSpan Source # | |
| AsRowSpan RowSpan Source # | |
| HasRowSpan RowSpan Source # | |
| RowSpan ~ t => Rewrapped RowSpan t Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| Walkable RowSpan RowSpan Source # | |
| type Rep RowSpan Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| type Unwrapped RowSpan Source # | |
Defined in Text.Pandoc.Z.Definition  | |
class HasRowSpan a where Source #
Instances
Instances
| Data ColSpan Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColSpan -> c ColSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColSpan # toConstr :: ColSpan -> Constr # dataTypeOf :: ColSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpan) # gmapT :: (forall b. Data b => b -> b) -> ColSpan -> ColSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> ColSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ColSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColSpan -> m ColSpan #  | |
| Monoid ColSpan Source # | |
| Semigroup ColSpan Source # | |
| Generic ColSpan Source # | |
| Num ColSpan Source # | |
| Read ColSpan Source # | |
| Show ColSpan Source # | |
| Eq ColSpan Source # | |
| Ord ColSpan Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| Wrapped ColSpan Source # | |
| AsColSpan ColSpan Source # | |
| HasColSpan ColSpan Source # | |
| ColSpan ~ t => Rewrapped ColSpan t Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| Walkable ColSpan ColSpan Source # | |
| type Rep ColSpan Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| type Unwrapped ColSpan Source # | |
Defined in Text.Pandoc.Z.Definition  | |
class HasColSpan a where Source #
Instances
Instances
Instances
| Data Row Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Row -> c Row # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Row # dataTypeOf :: Row -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Row) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Row) # gmapT :: (forall b. Data b => b -> b) -> Row -> Row # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r # gmapQ :: (forall d. Data d => d -> u) -> Row -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Row -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Row -> m Row # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Row -> m Row # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Row -> m Row #  | |
| Monoid Row Source # | |
| Semigroup Row Source # | |
| Generic Row Source # | |
| Read Row Source # | |
| Show Row Source # | |
| Eq Row Source # | |
| Ord Row Source # | |
| AsRow Row Source # | |
| HasAttr Row Source # | |
| HasRow Row Source # | |
| Walkable Row Row Source # | |
| type Rep Row Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Row = D1 ('MetaData "Row" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Row" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Cell])))  | |
Minimal complete definition
Instances
class HasTableHead a where Source #
Minimal complete definition
Instances
class AsTableHead a where Source #
Methods
_TableHead :: Prism' a TableHead Source #
Instances
| AsTableHead TableHead Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
| AsTableHead TableHead Source # | |
Defined in Text.Pandoc.Z.Definition  | |
newtype RowHeadColumns Source #
Constructors
| RowHeadColumns RowHeadColumns | 
Instances
class HasRowHeadColumns a where Source #
Methods
Instances
| HasRowHeadColumns RowHeadColumns Source # | |
Defined in Text.Pandoc.Z.Definition Methods rowHeadColumns :: Lens' RowHeadColumns RowHeadColumns0 Source #  | |
| HasRowHeadColumns RowHeadColumns Source # | |
Defined in Text.Pandoc.Z.Definition Methods rowHeadColumns :: Lens' RowHeadColumns RowHeadColumns Source #  | |
| HasRowHeadColumns TableBody Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
class AsRowHeadColumns a where Source #
Methods
Instances
| AsRowHeadColumns RowHeadColumns Source # | |
Defined in Text.Pandoc.Z.Definition Methods _RowHeadColumns :: Prism' RowHeadColumns RowHeadColumns0 Source #  | |
| AsRowHeadColumns RowHeadColumns Source # | |
Defined in Text.Pandoc.Z.Definition Methods _RowHeadColumns :: Prism' RowHeadColumns RowHeadColumns Source #  | |
Constructors
| TableBody Attr RowHeadColumns [Row] [Row] | 
Instances
class HasTableBody a where Source #
Minimal complete definition
Methods
tableBody :: Lens' a TableBody Source #
tableBodyRows1 :: Lens' a [Row] Source #
tableBodyRows2 :: Lens' a [Row] Source #
Instances
class AsTableBody a where Source #
Methods
_TableBody :: Prism' a TableBody Source #
Instances
| AsTableBody TableBody Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
| AsTableBody TableBody Source # | |
Defined in Text.Pandoc.Z.Definition  | |
Instances
class HasTableFoot a where Source #
Minimal complete definition
Instances
class AsTableFoot a where Source #
Methods
_TableFoot :: Prism' a TableFoot Source #
Instances
| AsTableFoot TableFoot Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
| AsTableFoot TableFoot Source # | |
Defined in Text.Pandoc.Z.Definition  | |
data Definition Source #
Constructors
| Definition [Inline] [[Block]] | 
Instances
class HasDefinition a where Source #
Minimal complete definition
Instances
| HasDefinition Definition Source # | |
Defined in Text.Pandoc.Z.Definition Methods definition :: Lens' Definition Definition Source # definitionBlocks :: Lens' Definition [[Block]] Source #  | |
class AsDefinition a where Source #
Methods
_Definition :: Prism' a Definition Source #
Instances
| AsDefinition Definition Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
Instances
| Data Header Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Header -> c Header # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Header # toConstr :: Header -> Constr # dataTypeOf :: Header -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Header) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header) # gmapT :: (forall b. Data b => b -> b) -> Header -> Header # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r # gmapQ :: (forall d. Data d => d -> u) -> Header -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Header -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Header -> m Header # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Header -> m Header # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Header -> m Header #  | |
| Generic Header Source # | |
| Read Header Source # | |
| Show Header Source # | |
| Eq Header Source # | |
| Ord Header Source # | |
| AsHeader Header Source # | |
| HasAttr Header Source # | |
| HasHeader Header Source # | |
| HasInlines Header Source # | |
| type Rep Header Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Header = D1 ('MetaData "Header" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Header" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Inline]))))  | |
data OrderedList Source #
Constructors
| OrderedList ListAttributes [[Block]] | 
Instances
class HasOrderedList a where Source #
Minimal complete definition
Instances
| HasOrderedList OrderedList Source # | |
Defined in Text.Pandoc.Z.Definition Methods orderedList :: Lens' OrderedList OrderedList Source # orderedListBlocks :: Lens' OrderedList [[Block]] Source #  | |
class AsOrderedList a where Source #
Methods
_OrderedList :: Prism' a OrderedList Source #
Instances
| AsOrderedList Block Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
| AsOrderedList Block Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
| AsOrderedList OrderedList Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
Instances
| Data Code Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Code -> c Code # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Code # dataTypeOf :: Code -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Code) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Code) # gmapT :: (forall b. Data b => b -> b) -> Code -> Code # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r # gmapQ :: (forall d. Data d => d -> u) -> Code -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Code -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Code -> m Code # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Code -> m Code # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Code -> m Code #  | |
| Monoid Code Source # | |
| Semigroup Code Source # | |
| Generic Code Source # | |
| Read Code Source # | |
| Show Code Source # | |
| Eq Code Source # | |
| Ord Code Source # | |
| AsCode Code Source # | |
| HasAttr Code Source # | |
| HasCode Code Source # | |
| HasText Code Source # | |
| type Rep Code Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Code = D1 ('MetaData "Code" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Code" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))  | |
Instances
| Data Raw Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Raw -> c Raw # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Raw # dataTypeOf :: Raw -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Raw) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Raw) # gmapT :: (forall b. Data b => b -> b) -> Raw -> Raw # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Raw -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Raw -> r # gmapQ :: (forall d. Data d => d -> u) -> Raw -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Raw -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Raw -> m Raw # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Raw -> m Raw # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Raw -> m Raw #  | |
| Generic Raw Source # | |
| Read Raw Source # | |
| Show Raw Source # | |
| Eq Raw Source # | |
| Ord Raw Source # | |
| AsRaw Raw Source # | |
| HasRaw Raw Source # | |
| HasText Raw Source # | |
| type Rep Raw Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Raw = D1 ('MetaData "Raw" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Raw" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Format) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))  | |
Instances
class HasTable a where Source #
Minimal complete definition
Instances
Instances
| Data Div Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Div -> c Div # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Div # dataTypeOf :: Div -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Div) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Div) # gmapT :: (forall b. Data b => b -> b) -> Div -> Div # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Div -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Div -> r # gmapQ :: (forall d. Data d => d -> u) -> Div -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Div -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Div -> m Div # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Div -> m Div # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Div -> m Div #  | |
| Monoid Div Source # | |
| Semigroup Div Source # | |
| Generic Div Source # | |
| Read Div Source # | |
| Show Div Source # | |
| Eq Div Source # | |
| Ord Div Source # | |
| AsDiv Div Source # | |
| HasBlocks Div Source # | |
| HasDiv Div Source # | |
| type Rep Div Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Div = D1 ('MetaData "Div" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Div" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block])))  | |
Constructors
Instances
class AsBlock a where Source #
Minimal complete definition
Methods
_Block :: Prism' a Block Source #
_Plain :: Prism' a [Inline] Source #
_Para :: Prism' a [Inline] Source #
_LineBlock :: Prism' a [[Inline]] Source #
_BlockQuote :: Prism' a [Block] Source #
_BulletList :: Prism' a [[Block]] Source #
_DefinitionList :: Prism' a [Definition] Source #
_HorizontalRule :: Prism' a () Source #
Instances
| AsBlock Block Source # | |
Defined in Text.Pandoc.Z.Definition Methods _Block :: Prism' Block Block0 Source # _Plain :: Prism' Block [Inline] Source # _Para :: Prism' Block [Inline] Source # _LineBlock :: Prism' Block [[Inline]] Source # _BlockQuote :: Prism' Block [Block0] Source # _BulletList :: Prism' Block [[Block0]] Source # _DefinitionList :: Prism' Block [Definition] Source # _HorizontalRule :: Prism' Block () Source #  | |
| AsBlock Block Source # | |
Defined in Text.Pandoc.Z.Definition Methods _Block :: Prism' Block Block Source # _Plain :: Prism' Block [Inline] Source # _Para :: Prism' Block [Inline] Source # _LineBlock :: Prism' Block [[Inline]] Source # _BlockQuote :: Prism' Block [Block] Source # _BulletList :: Prism' Block [[Block]] Source # _DefinitionList :: Prism' Block [Definition] Source # _HorizontalRule :: Prism' Block () Source #  | |
Constructors
| DisplayMath | |
| InlineMath | 
Instances
| Data MathType Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MathType -> c MathType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MathType # toConstr :: MathType -> Constr # dataTypeOf :: MathType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MathType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathType) # gmapT :: (forall b. Data b => b -> b) -> MathType -> MathType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MathType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MathType -> r # gmapQ :: (forall d. Data d => d -> u) -> MathType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MathType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MathType -> m MathType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MathType -> m MathType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MathType -> m MathType #  | |
| Generic MathType Source # | |
| Read MathType Source # | |
| Show MathType Source # | |
| Eq MathType Source # | |
| Ord MathType Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| AsMathType MathType Source # | |
| HasMathType MathType Source # | |
| Walkable MathType MathType Source # | |
| type Rep MathType Source # | |
class HasMathType a where Source #
Instances
class AsMathType a where Source #
Minimal complete definition
Methods
_MathType :: Prism' a MathType Source #
_DisplayMath :: Prism' a () Source #
_InlineMath :: Prism' a () Source #
Instances
Instances
| Data Meta Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Meta -> c Meta # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Meta # dataTypeOf :: Meta -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Meta) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Meta) # gmapT :: (forall b. Data b => b -> b) -> Meta -> Meta # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r # gmapQ :: (forall d. Data d => d -> u) -> Meta -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Meta -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Meta -> m Meta # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Meta -> m Meta # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Meta -> m Meta #  | |
| Monoid Meta Source # | |
| Semigroup Meta Source # | |
| Generic Meta Source # | |
| Read Meta Source # | |
| Show Meta Source # | |
| Eq Meta Source # | |
| Ord Meta Source # | |
| At Meta Source # | |
| Ixed Meta Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| AsEmpty Meta Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| Wrapped Meta Source # | |
| AsMeta Meta Source # | |
| HasMeta Meta Source # | |
| Meta ~ t => Rewrapped Meta t Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| Walkable Meta Meta Source # | |
| Each Meta Meta MetaValue MetaValue Source # | |
| type Rep Meta Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| type Index Meta Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| type IxValue Meta Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| type Unwrapped Meta Source # | |
Constructors
| MetaMap (Map Text MetaValue) | |
| MetaList [MetaValue] | |
| MetaBool Bool | |
| MetaString Text | |
| MetaInlines [Inline] | |
| MetaBlocks [Block] | 
Instances
class HasMetaValue a where Source #
Instances
class AsMetaValue a where Source #
Minimal complete definition
Methods
_MetaValue :: Prism' a MetaValue Source #
_MetaMap :: Prism' a (Map Text MetaValue) Source #
_MetaList :: Prism' a [MetaValue] Source #
_MetaBool :: Prism' a Bool Source #
_MetaString :: Prism' a Text Source #
Instances
Constructors
| SingleQuote | |
| DoubleQuote | 
Instances
| Data QuoteType Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuoteType -> c QuoteType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuoteType # toConstr :: QuoteType -> Constr # dataTypeOf :: QuoteType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QuoteType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteType) # gmapT :: (forall b. Data b => b -> b) -> QuoteType -> QuoteType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r # gmapQ :: (forall d. Data d => d -> u) -> QuoteType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> QuoteType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType #  | |
| Generic QuoteType Source # | |
| Read QuoteType Source # | |
| Show QuoteType Source # | |
| Eq QuoteType Source # | |
| Ord QuoteType Source # | |
| AsQuoteType QuoteType Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| HasQuoteType QuoteType Source # | |
| Walkable QuoteType QuoteType Source # | |
Defined in Text.Pandoc.Z.Definition Methods walk :: (QuoteType0 -> QuoteType0) -> QuoteType -> QuoteType # walkM :: (Monad m, Applicative m, Functor m) => (QuoteType0 -> m QuoteType0) -> QuoteType -> m QuoteType # query :: Monoid c => (QuoteType0 -> c) -> QuoteType -> c #  | |
| type Rep QuoteType Source # | |
class HasQuoteType a where Source #
Instances
class AsQuoteType a where Source #
Minimal complete definition
Methods
_QuoteType :: Prism' a QuoteType Source #
_SingleQuote :: Prism' a () Source #
_DoubleQuote :: Prism' a () Source #
Instances
| AsQuoteType QuoteType Source # | |
Defined in Text.Pandoc.Z.Definition Methods _QuoteType :: Prism' QuoteType QuoteType0 Source # _SingleQuote :: Prism' QuoteType () Source # _DoubleQuote :: Prism' QuoteType () Source #  | |
| AsQuoteType QuoteType Source # | |
Defined in Text.Pandoc.Z.Definition  | |
newtype ShortCaption Source #
Constructors
| ShortCaption [Inline] | 
Instances
class HasShortCaption a where Source #
Methods
shortCaption :: Lens' a ShortCaption Source #
Instances
| HasShortCaption ShortCaption Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
| HasShortCaption ShortCaption Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
class AsShortCaption a where Source #
Methods
Instances
| AsShortCaption ShortCaption Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
| AsShortCaption ShortCaption Source # | |
Defined in Text.Pandoc.Z.Definition Methods  | |
Instances
| Data Target Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Target -> c Target # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Target # toConstr :: Target -> Constr # dataTypeOf :: Target -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Target) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Target) # gmapT :: (forall b. Data b => b -> b) -> Target -> Target # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Target -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Target -> r # gmapQ :: (forall d. Data d => d -> u) -> Target -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Target -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Target -> m Target # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Target -> m Target # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Target -> m Target #  | |
| Monoid Target Source # | |
| Semigroup Target Source # | |
| Generic Target Source # | |
| Read Target Source # | |
| Show Target Source # | |
| Eq Target Source # | |
| Ord Target Source # | |
| AsTarget Target Source # | |
| HasTarget Target Source # | |
| Walkable Target Target Source # | |
| type Rep Target Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Target = D1 ('MetaData "Target" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Target" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))  | |
class HasTarget a where Source #
Minimal complete definition
Methods
target :: Lens' a Target Source #
targetURL :: Lens' a Text Source #
targetTitle :: Lens' a Text Source #
Instances
| Data Link Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Link -> c Link # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Link # dataTypeOf :: Link -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Link) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Link) # gmapT :: (forall b. Data b => b -> b) -> Link -> Link # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r # gmapQ :: (forall d. Data d => d -> u) -> Link -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Link -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Link -> m Link # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Link -> m Link # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Link -> m Link #  | |
| Monoid Link Source # | |
| Semigroup Link Source # | |
| Generic Link Source # | |
| Read Link Source # | |
| Show Link Source # | |
| Eq Link Source # | |
| Ord Link Source # | |
| AsLink Link Source # | |
| HasAttr Link Source # | |
| HasInlines Link Source # | |
| HasLink Link Source # | |
| HasSpan Link Source # | |
| HasTarget Link Source # | |
| type Rep Link Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Link = D1 ('MetaData "Link" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Link" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Inline]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Target))))  | |
Instances
| Data Image Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Image -> c Image # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Image # dataTypeOf :: Image -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Image) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image) # gmapT :: (forall b. Data b => b -> b) -> Image -> Image # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r # gmapQ :: (forall d. Data d => d -> u) -> Image -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Image -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Image -> m Image # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image #  | |
| Monoid Image Source # | |
| Semigroup Image Source # | |
| Generic Image Source # | |
| Read Image Source # | |
| Show Image Source # | |
| Eq Image Source # | |
| Ord Image Source # | |
| AsImage Image Source # | |
| HasAttr Image Source # | |
| HasImage Image Source # | |
| HasInlines Image Source # | |
| HasSpan Image Source # | |
| HasTarget Image Source # | |
| type Rep Image Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Image = D1 ('MetaData "Image" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Image" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Inline]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Target))))  | |
Instances
| Data Span Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Span -> c Span # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Span # dataTypeOf :: Span -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Span) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Span) # gmapT :: (forall b. Data b => b -> b) -> Span -> Span # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r # gmapQ :: (forall d. Data d => d -> u) -> Span -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Span -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Span -> m Span # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span #  | |
| Monoid Span Source # | |
| Semigroup Span Source # | |
| Generic Span Source # | |
| Read Span Source # | |
| Show Span Source # | |
| Eq Span Source # | |
| Ord Span Source # | |
| AsSpan Span Source # | |
| HasAttr Span Source # | |
| HasInlines Span Source # | |
| HasSpan Span Source # | |
| type Rep Span Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Span = D1 ('MetaData "Span" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Span" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Inline])))  | |
Instances
| Data Quoted Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Quoted -> c Quoted # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Quoted # toConstr :: Quoted -> Constr # dataTypeOf :: Quoted -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Quoted) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Quoted) # gmapT :: (forall b. Data b => b -> b) -> Quoted -> Quoted # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Quoted -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Quoted -> r # gmapQ :: (forall d. Data d => d -> u) -> Quoted -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Quoted -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Quoted -> m Quoted # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Quoted -> m Quoted # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Quoted -> m Quoted #  | |
| Generic Quoted Source # | |
| Read Quoted Source # | |
| Show Quoted Source # | |
| Eq Quoted Source # | |
| Ord Quoted Source # | |
| AsQuoted Quoted Source # | |
| HasInlines Quoted Source # | |
| HasQuoteType Quoted Source # | |
| HasQuoted Quoted Source # | |
| type Rep Quoted Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Quoted = D1 ('MetaData "Quoted" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Quoted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QuoteType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Inline])))  | |
Instances
| Data Cite Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cite -> c Cite # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cite # dataTypeOf :: Cite -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cite) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cite) # gmapT :: (forall b. Data b => b -> b) -> Cite -> Cite # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r # gmapQ :: (forall d. Data d => d -> u) -> Cite -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Cite -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cite -> m Cite # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cite -> m Cite # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cite -> m Cite #  | |
| Monoid Cite Source # | |
| Semigroup Cite Source # | |
| Generic Cite Source # | |
| Read Cite Source # | |
| Show Cite Source # | |
| Eq Cite Source # | |
| Ord Cite Source # | |
| AsCite Cite Source # | |
| HasCite Cite Source # | |
| HasInlines Cite Source # | |
| type Rep Cite Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Cite = D1 ('MetaData "Cite" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Cite" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Citation]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Inline])))  | |
Instances
| Data Math Source # | |
Defined in Text.Pandoc.Z.Definition Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Math -> c Math # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Math # dataTypeOf :: Math -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Math) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Math) # gmapT :: (forall b. Data b => b -> b) -> Math -> Math # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Math -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Math -> r # gmapQ :: (forall d. Data d => d -> u) -> Math -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Math -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Math -> m Math # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Math -> m Math # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Math -> m Math #  | |
| Generic Math Source # | |
| Read Math Source # | |
| Show Math Source # | |
| Eq Math Source # | |
| Ord Math Source # | |
| AsMath Math Source # | |
| HasMath Math Source # | |
| HasMathType Math Source # | |
| HasText Math Source # | |
| type Rep Math Source # | |
Defined in Text.Pandoc.Z.Definition type Rep Math = D1 ('MetaData "Math" "Text.Pandoc.Z.Definition" "pandocz-0.0.2-1iLYLffzu2BBmJdXaVPw4E" 'False) (C1 ('MetaCons "Math" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MathType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))  | |
Constructors
Instances
class AsInline a where Source #
Minimal complete definition
Methods
_Inline :: Prism' a Inline Source #
_Str :: Prism' a Text Source #
_Emph :: Prism' a [Inline] Source #
_Underline :: Prism' a [Inline] Source #
_Strong :: Prism' a [Inline] Source #
_Strikeout :: Prism' a [Inline] Source #
_Superscript :: Prism' a [Inline] Source #
_Subscript :: Prism' a [Inline] Source #
_SmallCaps :: Prism' a [Inline] Source #
_Space :: Prism' a () Source #
_SoftBreak :: Prism' a () Source #
_LineBreak :: Prism' a () Source #
Instances
Instances
class HasCitation a where Source #
Minimal complete definition
Methods
citation :: Lens' a Citation Source #
citationId :: Lens' a Text Source #
citationPrefix :: Lens' a [Inline] Source #
citationSuffix :: Lens' a [Inline] Source #
citationNoteNum :: Lens' a Int Source #
citationHash :: Lens' a Int Source #
Instances
| HasCitation Citation Source # | |
Defined in Text.Pandoc.Z.Definition  | |
| HasCitation Citation Source # | |
Defined in Text.Pandoc.Z.Definition  | |
class AsCitation a where Source #
class HasInlines a where Source #