| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Commonmark.Inlines
Synopsis
- mkInlineParser :: (Monad m, IsInline a) => [BracketedSpec a] -> [FormattingSpec a] -> [InlineParser m a] -> [InlineParser m Attributes] -> ReferenceMap -> [Tok] -> m (Either ParseError a)
- defaultInlineParser :: (Monad m, IsInline a) => InlineParser m a
- data IPState m
- type InlineParser m = ParsecT [Tok] (IPState m) (StateT Enders m)
- getReferenceMap :: Monad m => InlineParser m ReferenceMap
- data FormattingSpec il = FormattingSpec {- formattingDelimChar :: !Char
- formattingIntraWord :: !Bool
- formattingIgnorePunctuation :: !Bool
- formattingSingleMatch :: Maybe (il -> il)
- formattingDoubleMatch :: Maybe (il -> il)
- formattingWhenUnmatched :: !Char
 
- defaultFormattingSpecs :: IsInline il => [FormattingSpec il]
- data BracketedSpec il = BracketedSpec {- bracketedName :: !Text
- bracketedNests :: !Bool
- bracketedPrefix :: Maybe Char
- bracketedSuffixEnd :: Maybe Char
- bracketedSuffix :: ReferenceMap -> Text -> Parsec [Tok] () (il -> il)
 
- defaultBracketedSpecs :: IsInline il => [BracketedSpec il]
- data LinkInfo = LinkInfo {- linkDestination :: !Text
- linkTitle :: !Text
- linkAttributes :: !Attributes
- linkPos :: !(Maybe SourcePos)
 
- imageSpec :: IsInline il => BracketedSpec il
- linkSpec :: IsInline il => BracketedSpec il
- pLink :: ReferenceMap -> Text -> Parsec [Tok] s LinkInfo
- pLinkLabel :: Monad m => ParsecT [Tok] s m Text
- pLinkDestination :: Monad m => ParsecT [Tok] s m [Tok]
- pLinkTitle :: Monad m => ParsecT [Tok] s m [Tok]
- pEscaped :: Monad m => ParsecT [Tok] s m Tok
- pEscapedSymbol :: Monad m => ParsecT [Tok] s m Tok
- processEmphasis :: IsInline a => [Chunk a] -> [Chunk a]
- processBrackets :: IsInline a => [BracketedSpec a] -> ReferenceMap -> [Chunk a] -> Map Text SourcePos -> Either (DState a) [Chunk a]
- pBacktickSpan :: Monad m => Tok -> InlineParser m (Either [Tok] [Tok])
- normalizeCodeSpan :: Text -> Text
- withAttributes :: (IsInline a, Monad m) => InlineParser m a -> InlineParser m a
Documentation
mkInlineParser :: (Monad m, IsInline a) => [BracketedSpec a] -> [FormattingSpec a] -> [InlineParser m a] -> [InlineParser m Attributes] -> ReferenceMap -> [Tok] -> m (Either ParseError a) Source #
defaultInlineParser :: (Monad m, IsInline a) => InlineParser m a Source #
type InlineParser m = ParsecT [Tok] (IPState m) (StateT Enders m) Source #
Specifies delimiters for formatting, e.g. strong emphasis.
getReferenceMap :: Monad m => InlineParser m ReferenceMap Source #
data FormattingSpec il Source #
Constructors
| FormattingSpec | |
| Fields 
 | |
Instances
| Show (FormattingSpec il) Source # | |
| Defined in Commonmark.Inlines Methods showsPrec :: Int -> FormattingSpec il -> ShowS # show :: FormattingSpec il -> String # showList :: [FormattingSpec il] -> ShowS # | |
defaultFormattingSpecs :: IsInline il => [FormattingSpec il] Source #
data BracketedSpec il Source #
Constructors
| BracketedSpec | |
| Fields 
 | |
Instances
| Show (BracketedSpec il) Source # | |
| Defined in Commonmark.Inlines Methods showsPrec :: Int -> BracketedSpec il -> ShowS # show :: BracketedSpec il -> String # showList :: [BracketedSpec il] -> ShowS # | |
defaultBracketedSpecs :: IsInline il => [BracketedSpec il] Source #
Constructors
| LinkInfo | |
| Fields 
 | |
imageSpec :: IsInline il => BracketedSpec il Source #
linkSpec :: IsInline il => BracketedSpec il Source #
processEmphasis :: IsInline a => [Chunk a] -> [Chunk a] Source #
processBrackets :: IsInline a => [BracketedSpec a] -> ReferenceMap -> [Chunk a] -> Map Text SourcePos -> Either (DState a) [Chunk a] Source #
Process square brackets: links, images, and the span extension.
DState tracks the current position and backtracking limits.
If this function succeeds, returning Right, it will return a list of
 chunks, now annotated with bracket information.
If this function fails, it will return `Left DState`. This can happen if a chunk straddles a link destination, like this
link text looks like code` ^-----------------^
To recover, the caller must re-Chunk everything after the end paren.
 The bottoms parameter, in particular, is DState's stackBottoms,
 and is used to prevent things before the paren from being re-parsed.
pBacktickSpan :: Monad m => Tok -> InlineParser m (Either [Tok] [Tok]) Source #
normalizeCodeSpan :: Text -> Text Source #
withAttributes :: (IsInline a, Monad m) => InlineParser m a -> InlineParser m a Source #