Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- commonmarkToHtml :: [CMarkOption] -> [CMarkExtension] -> Text -> Text
- commonmarkToXml :: [CMarkOption] -> [CMarkExtension] -> Text -> Text
- commonmarkToMan :: [CMarkOption] -> [CMarkExtension] -> Maybe Int -> Text -> Text
- commonmarkToLaTeX :: [CMarkOption] -> [CMarkExtension] -> Maybe Int -> Text -> Text
- commonmarkToNode :: [CMarkOption] -> [CMarkExtension] -> Text -> Node
- nodeToHtml :: [CMarkOption] -> [CMarkExtension] -> Node -> Text
- nodeToXml :: [CMarkOption] -> Node -> Text
- nodeToMan :: [CMarkOption] -> Maybe Int -> Node -> Text
- nodeToLaTeX :: [CMarkOption] -> Maybe Int -> Node -> Text
- nodeToCommonmark :: [CMarkOption] -> Maybe Int -> Node -> Text
- optSourcePos :: CMarkOption
- optHardBreaks :: CMarkOption
- optSmart :: CMarkOption
- optSafe :: CMarkOption
- optUnsafe :: CMarkOption
- optFootnotes :: CMarkOption
- extStrikethrough :: CMarkExtension
- extTable :: CMarkExtension
- extAutolink :: CMarkExtension
- extTagfilter :: CMarkExtension
- extTaskList :: CMarkExtension
- data Node = Node (Maybe PosInfo) NodeType [Node]
- data NodeType
- = DOCUMENT
- | THEMATIC_BREAK
- | PARAGRAPH
- | BLOCK_QUOTE
- | HTML_BLOCK Text
- | CUSTOM_BLOCK OnEnter OnExit
- | CODE_BLOCK Info Text
- | HEADING Level
- | LIST ListAttributes
- | ITEM
- | TEXT Text
- | SOFTBREAK
- | LINEBREAK
- | HTML_INLINE Text
- | CUSTOM_INLINE OnEnter OnExit
- | CODE Text
- | EMPH
- | STRONG
- | LINK Url Title
- | IMAGE Url Title
- | STRIKETHROUGH
- | TABLE [TableCellAlignment]
- | TABLE_ROW
- | TABLE_CELL
- | FOOTNOTE_REFERENCE
- | FOOTNOTE_DEFINITION
- data PosInfo = PosInfo {}
- data DelimType
- data ListType
- data ListAttributes = ListAttributes {}
- type Url = Text
- type Title = Text
- type Level = Int
- type Info = Text
- data TableCellAlignment
- data CMarkOption
- data CMarkExtension
Documentation
commonmarkToHtml :: [CMarkOption] -> [CMarkExtension] -> Text -> Text Source #
Convert CommonMark formatted text to Html, using cmark's built-in renderer.
commonmarkToXml :: [CMarkOption] -> [CMarkExtension] -> Text -> Text Source #
Convert CommonMark formatted text to CommonMark XML, using cmark's built-in renderer.
commonmarkToMan :: [CMarkOption] -> [CMarkExtension] -> Maybe Int -> Text -> Text Source #
Convert CommonMark formatted text to groff man, using cmark's built-in renderer.
commonmarkToLaTeX :: [CMarkOption] -> [CMarkExtension] -> Maybe Int -> Text -> Text Source #
Convert CommonMark formatted text to latex, using cmark's built-in renderer.
commonmarkToNode :: [CMarkOption] -> [CMarkExtension] -> Text -> Node Source #
Convert CommonMark formatted text to a structured Node
tree,
which can be transformed or rendered using Haskell code.
nodeToHtml :: [CMarkOption] -> [CMarkExtension] -> Node -> Text Source #
nodeToLaTeX :: [CMarkOption] -> Maybe Int -> Node -> Text Source #
nodeToCommonmark :: [CMarkOption] -> Maybe Int -> Node -> Text Source #
optSourcePos :: CMarkOption Source #
Include a data-sourcepos
attribute on block elements.
optHardBreaks :: CMarkOption Source #
Render softbreak
elements as hard line breaks.
optSmart :: CMarkOption Source #
Convert straight quotes to curly, ---
to em-dash, --
to en-dash.
optSafe :: CMarkOption Source #
optSafe is defined here for API compatibility, but it no longer has any effect. Safe mode is now the default: set optUnsafe to disable it.
optUnsafe :: CMarkOption Source #
Allow rendering of raw HTML and potentially dangerous URLs in links and images.
optFootnotes :: CMarkOption Source #
Enable footnote syntax support (equivalent of footnotes extension for official cmark-gfm)
Instances
Data Node Source # | |
Defined in CMarkGFM gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Node -> c Node # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Node # dataTypeOf :: Node -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Node) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Node) # gmapT :: (forall b. Data b => b -> b) -> Node -> Node # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r # gmapQ :: (forall d. Data d => d -> u) -> Node -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Node -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Node -> m Node # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Node -> m Node # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Node -> m Node # | |
Generic Node Source # | |
Read Node Source # | |
Show Node Source # | |
Eq Node Source # | |
Ord Node Source # | |
type Rep Node Source # | |
Defined in CMarkGFM type Rep Node = D1 ('MetaData "Node" "CMarkGFM" "cmark-gfm-0.2.6-G3rZtSwpqpk8LVz00lSWZb" 'False) (C1 ('MetaCons "Node" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PosInfo)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NodeType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Node])))) |
Instances
Data NodeType Source # | |
Defined in CMarkGFM gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NodeType -> c NodeType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NodeType # toConstr :: NodeType -> Constr # dataTypeOf :: NodeType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NodeType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NodeType) # gmapT :: (forall b. Data b => b -> b) -> NodeType -> NodeType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NodeType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NodeType -> r # gmapQ :: (forall d. Data d => d -> u) -> NodeType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NodeType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NodeType -> m NodeType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NodeType -> m NodeType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NodeType -> m NodeType # | |
Generic NodeType Source # | |
Read NodeType Source # | |
Show NodeType Source # | |
Eq NodeType Source # | |
Ord NodeType Source # | |
type Rep NodeType Source # | |
Instances
Data PosInfo Source # | |
Defined in CMarkGFM gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosInfo -> c PosInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosInfo # toConstr :: PosInfo -> Constr # dataTypeOf :: PosInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PosInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosInfo) # gmapT :: (forall b. Data b => b -> b) -> PosInfo -> PosInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosInfo -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> PosInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PosInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosInfo -> m PosInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosInfo -> m PosInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosInfo -> m PosInfo # | |
Generic PosInfo Source # | |
Read PosInfo Source # | |
Show PosInfo Source # | |
Eq PosInfo Source # | |
Ord PosInfo Source # | |
type Rep PosInfo Source # | |
Defined in CMarkGFM type Rep PosInfo = D1 ('MetaData "PosInfo" "CMarkGFM" "cmark-gfm-0.2.6-G3rZtSwpqpk8LVz00lSWZb" 'False) (C1 ('MetaCons "PosInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "startLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "startColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "endLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "endColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))) |
Instances
Data DelimType Source # | |
Defined in CMarkGFM gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DelimType -> c DelimType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DelimType # toConstr :: DelimType -> Constr # dataTypeOf :: DelimType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DelimType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DelimType) # gmapT :: (forall b. Data b => b -> b) -> DelimType -> DelimType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DelimType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DelimType -> r # gmapQ :: (forall d. Data d => d -> u) -> DelimType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DelimType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DelimType -> m DelimType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DelimType -> m DelimType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DelimType -> m DelimType # | |
Generic DelimType Source # | |
Read DelimType Source # | |
Show DelimType Source # | |
Eq DelimType Source # | |
Ord DelimType Source # | |
Defined in CMarkGFM | |
type Rep DelimType Source # | |
Instances
Data ListType Source # | |
Defined in CMarkGFM gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListType -> c ListType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListType # toConstr :: ListType -> Constr # dataTypeOf :: ListType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListType) # gmapT :: (forall b. Data b => b -> b) -> ListType -> ListType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListType -> r # gmapQ :: (forall d. Data d => d -> u) -> ListType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ListType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListType -> m ListType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListType -> m ListType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListType -> m ListType # | |
Generic ListType Source # | |
Read ListType Source # | |
Show ListType Source # | |
Eq ListType Source # | |
Ord ListType Source # | |
type Rep ListType Source # | |
data ListAttributes Source #
Instances
data TableCellAlignment Source #
Instances
data CMarkOption Source #
data CMarkExtension Source #