mmark-0.0.7.6: Strict markdown processor for writers
Copyright© 2017–present Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <[email protected]>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.MMark.Extension

Description

This module provides building blocks for creation of extensions.

We suggest using a qualified import, like this:

import Text.MMark.Extension (Bni, Block (..), Inline (..))
import qualified Text.MMark.Extension as Ext

The philosophy of MMark extensions

The extension system is guided by the following goals:

  1. Make it powerful, so users can write interesting extensions.
  2. Make it efficient, so every type of transformation is only applied once and the number of traversals of the syntax tree stays constant no matter how many extensions the user chooses to use and how complex they are.
  3. Make it easy to write extensions that are very focused in what they do and do not interfere with each other in weird and unexpected ways.

I ruled out allowing users to mess with AST directly pretty quickly because it would be against the points 2 and 3. Instead, there are four kinds of extension-producing functions. They correspond internally to four functions that are applied to the parsed document in turn:

  • blockTrans is applied first, as it's quite general and can change block-level structure of document as well as inline-level structure.
  • inlineTrans is applied to every inline in the document obtained in the previous step.
  • inlineRender is applied to every inline; this function produces HTML rendition of the inlines and we also preserve the original inlines so blockRender can look at it (see Ois).
  • blockRender is applied to every block to obtain HTML rendition of the whole document.

When one combines different extensions, extensions of the same kind get fused together into a single function. This allows for faster processing and constant number of traversals over AST in the end.

One could note that the current design does not allow prepending or appending new elements to the AST. This is a limitation by design because we try to make the order in which extensions are applied unimportant (it's not always possible, though). Thus, if we want to e.g. insert a table of contents into a document, we need to do so by transforming an already existing element, such as code block with a special info string (this is how the extension works in the mmark-ext package).

Another limitation by design is that extensions cannot change how the parser works. I find endless syntax-changing (or syntax-augmenting, if you will) extensions (as implemented by Pandoc for example) ugly, because they erode the familiar markdown syntax and turn it into a monstrosity. In MMark we choose a different path of re-purposing existing markdown constructs, adding special meaning to them in certain situations.

Room for improvement

One flaw of the current system is that it does not allow reporting errors, so we have to silently fallback to some default behavior when we can't apply an extension in a meaningful way. Such extension-produced errors obviously should contain their positions in the original markdown input, which would require us storing this information in AST in some way. I'm not sure if the additional complexity (and possible performance trade-offs) is really worth it, so it hasn't been implemented so far.

Synopsis

Extension construction

data Extension Source #

An extension. You can apply extensions with useExtension and useExtensions functions. The Text.MMark.Extension module provides tools for writing your own extensions.

Note that Extension is an instance of Semigroup and Monoid, i.e. you can combine several extensions into one. Since the (<>) operator is right-associative and mconcat is a right fold under the hood, the expression

l <> r

means that the extension r will be applied before the extension l, similar to how Endo works. This may seem counter-intuitive, but only with this logic we get consistency of ordering with more complex expressions:

e2 <> e1 <> e0 == e2 <> (e1 <> e0)

Here, e0 will be applied first, then e1, then e2. The same applies to expressions involving mconcat—extensions closer to beginning of the list passed to mconcat will be applied later.

Instances

Instances details
Semigroup Extension Source # 
Instance details

Defined in Text.MMark.Type

Monoid Extension Source # 
Instance details

Defined in Text.MMark.Type

Block-level manipulation

type Bni = Block (NonEmpty Inline) Source #

A shortcut for the frequently used type Block (NonEmpty Inline).

data Block a Source #

We can think of a markdown document as a collection of blocks—structural elements like paragraphs, block quotations, lists, headings, thematic breaks, and code blocks. Some blocks (like block quotes and list items) contain other blocks; others (like headings and paragraphs) contain inline content, see Inline.

We can divide blocks into two types: container blocks, which can contain other blocks, and leaf blocks, which cannot.

Constructors

ThematicBreak

Thematic break, leaf block

Heading1 a

Heading (level 1), leaf block

Heading2 a

Heading (level 2), leaf block

Heading3 a

Heading (level 3), leaf block

Heading4 a

Heading (level 4), leaf block

Heading5 a

Heading (level 5), leaf block

Heading6 a

Heading (level 6), leaf block

CodeBlock (Maybe Text) Text

Code block, leaf block with info string and contents

Naked a

Naked content, without an enclosing tag

Paragraph a

Paragraph, leaf block

Blockquote [Block a]

Blockquote container block

OrderedList Word (NonEmpty [Block a])

Ordered list (Word is the start index), container block

UnorderedList (NonEmpty [Block a])

Unordered list, container block

Table (NonEmpty CellAlign) (NonEmpty (NonEmpty a))

Table, first argument is the alignment options, then we have a NonEmpty list of rows, where every row is a NonEmpty list of cells, where every cell is an a thing.

The first row is always the header row, because pipe-tables that we support cannot lack a header row.

Since: 0.0.4.0

Instances

Instances details
Functor Block Source # 
Instance details

Defined in Text.MMark.Type

Methods

fmap :: (a -> b) -> Block a -> Block b #

(<$) :: a -> Block b -> Block a #

Foldable Block Source # 
Instance details

Defined in Text.MMark.Type

Methods

fold :: Monoid m => Block m -> m #

foldMap :: Monoid m => (a -> m) -> Block a -> m #

foldMap' :: Monoid m => (a -> m) -> Block a -> m #

foldr :: (a -> b -> b) -> b -> Block a -> b #

foldr' :: (a -> b -> b) -> b -> Block a -> b #

foldl :: (b -> a -> b) -> b -> Block a -> b #

foldl' :: (b -> a -> b) -> b -> Block a -> b #

foldr1 :: (a -> a -> a) -> Block a -> a #

foldl1 :: (a -> a -> a) -> Block a -> a #

toList :: Block a -> [a] #

null :: Block a -> Bool #

length :: Block a -> Int #

elem :: Eq a => a -> Block a -> Bool #

maximum :: Ord a => Block a -> a #

minimum :: Ord a => Block a -> a #

sum :: Num a => Block a -> a #

product :: Num a => Block a -> a #

Eq a => Eq (Block a) Source # 
Instance details

Defined in Text.MMark.Type

Methods

(==) :: Block a -> Block a -> Bool #

(/=) :: Block a -> Block a -> Bool #

Data a => Data (Block a) Source # 
Instance details

Defined in Text.MMark.Type

Methods

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

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

toConstr :: Block a -> Constr #

dataTypeOf :: Block a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Block a) Source # 
Instance details

Defined in Text.MMark.Type

Methods

compare :: Block a -> Block a -> Ordering #

(<) :: Block a -> Block a -> Bool #

(<=) :: Block a -> Block a -> Bool #

(>) :: Block a -> Block a -> Bool #

(>=) :: Block a -> Block a -> Bool #

max :: Block a -> Block a -> Block a #

min :: Block a -> Block a -> Block a #

Show a => Show (Block a) Source # 
Instance details

Defined in Text.MMark.Type

Methods

showsPrec :: Int -> Block a -> ShowS #

show :: Block a -> String #

showList :: [Block a] -> ShowS #

Generic (Block a) Source # 
Instance details

Defined in Text.MMark.Type

Associated Types

type Rep (Block a) :: Type -> Type #

Methods

from :: Block a -> Rep (Block a) x #

to :: Rep (Block a) x -> Block a #

NFData a => NFData (Block a) Source # 
Instance details

Defined in Text.MMark.Type

Methods

rnf :: Block a -> () #

type Rep (Block a) Source # 
Instance details

Defined in Text.MMark.Type

type Rep (Block a) = D1 ('MetaData "Block" "Text.MMark.Type" "mmark-0.0.7.6-5Qnx7bFCHBRCxrgZMMJO8j" 'False) (((C1 ('MetaCons "ThematicBreak" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Heading1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Heading2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) :+: ((C1 ('MetaCons "Heading3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Heading4" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) :+: (C1 ('MetaCons "Heading5" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Heading6" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))) :+: ((C1 ('MetaCons "CodeBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "Naked" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Paragraph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) :+: ((C1 ('MetaCons "Blockquote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block a])) :+: C1 ('MetaCons "OrderedList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty [Block a])))) :+: (C1 ('MetaCons "UnorderedList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty [Block a]))) :+: C1 ('MetaCons "Table" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty CellAlign)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (NonEmpty a))))))))

data CellAlign Source #

Options for cell alignment in tables.

Since: 0.0.4.0

Constructors

CellAlignDefault

No specific alignment specified

CellAlignLeft

Left-alignment

CellAlignRight

Right-alignment

CellAlignCenter

Center-alignment

Instances

Instances details
Eq CellAlign Source # 
Instance details

Defined in Text.MMark.Type

Data CellAlign Source # 
Instance details

Defined in Text.MMark.Type

Methods

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

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

toConstr :: CellAlign -> Constr #

dataTypeOf :: CellAlign -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CellAlign Source # 
Instance details

Defined in Text.MMark.Type

Show CellAlign Source # 
Instance details

Defined in Text.MMark.Type

Generic CellAlign Source # 
Instance details

Defined in Text.MMark.Type

Associated Types

type Rep CellAlign :: Type -> Type #

NFData CellAlign Source # 
Instance details

Defined in Text.MMark.Type

Methods

rnf :: CellAlign -> () #

type Rep CellAlign Source # 
Instance details

Defined in Text.MMark.Type

type Rep CellAlign = D1 ('MetaData "CellAlign" "Text.MMark.Type" "mmark-0.0.7.6-5Qnx7bFCHBRCxrgZMMJO8j" 'False) ((C1 ('MetaCons "CellAlignDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CellAlignLeft" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CellAlignRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CellAlignCenter" 'PrefixI 'False) (U1 :: Type -> Type)))

blockTrans :: (Bni -> Bni) -> Extension Source #

Create an extension that performs a transformation on Blocks of markdown document. Since a block may contain other blocks we choose to perform transformations from the most deeply nested blocks moving upwards. This has the benefit that the result of any transformation is final in the sense that sub-elements of resulting block won't be traversed again.

blockRender :: ((Block (Ois, Html ()) -> Html ()) -> Block (Ois, Html ()) -> Html ()) -> Extension Source #

Create an extension that replaces or augments rendering of Blocks of markdown document. The argument of blockRender will be given the rendering function constructed so far Block (Ois, Html ()) -> Html () as well as an actual block to render—Block (Ois, Html ()). The user can then decide whether to replace/reuse that function to get the final rendering of the type Html ().

The argument of blockRender can also be thought of as a function that transforms the rendering function constructed so far:

(Block (Ois, Html ()) -> Html ()) -> (Block (Ois, Html ()) -> Html ())

See also: Ois and getOis.

data Ois Source #

A wrapper for “original inlines”. Source inlines are wrapped in this during rendering of inline components and then it's available to block render, but only for inspection. Altering of Ois is not possible because the user cannot construct a value of the Ois type, he/she can only inspect it with getOis.

Inline-level manipulation

data Inline Source #

Inline markdown content.

Constructors

Plain Text

Plain text

LineBreak

Line break (hard)

Emphasis (NonEmpty Inline)

Emphasis

Strong (NonEmpty Inline)

Strong emphasis

Strikeout (NonEmpty Inline)

Strikeout

Subscript (NonEmpty Inline)

Subscript

Superscript (NonEmpty Inline)

Superscript

CodeSpan Text

Code span

Link (NonEmpty Inline) URI (Maybe Text)

Link with text, destination, and optionally title

Image (NonEmpty Inline) URI (Maybe Text)

Image with description, URL, and optionally title

Instances

Instances details
Eq Inline Source # 
Instance details

Defined in Text.MMark.Type

Methods

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

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

Data Inline Source # 
Instance details

Defined in Text.MMark.Type

Methods

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

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

toConstr :: Inline -> Constr #

dataTypeOf :: Inline -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Inline Source # 
Instance details

Defined in Text.MMark.Type

Show Inline Source # 
Instance details

Defined in Text.MMark.Type

Generic Inline Source # 
Instance details

Defined in Text.MMark.Type

Associated Types

type Rep Inline :: Type -> Type #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

NFData Inline Source # 
Instance details

Defined in Text.MMark.Type

Methods

rnf :: Inline -> () #

type Rep Inline Source # 
Instance details

Defined in Text.MMark.Type

type Rep Inline = D1 ('MetaData "Inline" "Text.MMark.Type" "mmark-0.0.7.6-5Qnx7bFCHBRCxrgZMMJO8j" 'False) (((C1 ('MetaCons "Plain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "LineBreak" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Emphasis" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Inline))) :+: (C1 ('MetaCons "Strong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Inline))) :+: C1 ('MetaCons "Strikeout" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Inline)))))) :+: ((C1 ('MetaCons "Subscript" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Inline))) :+: C1 ('MetaCons "Superscript" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Inline)))) :+: (C1 ('MetaCons "CodeSpan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "Link" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Inline)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 URI) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :+: C1 ('MetaCons "Image" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Inline)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 URI) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))))))

inlineTrans :: (Inline -> Inline) -> Extension Source #

Create an extension that performs a transformation on Inline components in entire markdown document. Similarly to blockTrans the transformation is applied from the most deeply nested elements moving upwards.

inlineRender :: ((Inline -> Html ()) -> Inline -> Html ()) -> Extension Source #

Create an extension that replaces or augments rendering of Inlines of markdown document. This works like blockRender.

Scanner construction

scanner Source #

Arguments

:: a

Initial state

-> (a -> Bni -> a)

Folding function

-> Fold Bni a

Resulting Fold

Create a Fold from an initial state and a folding function.

scannerM Source #

Arguments

:: Monad m 
=> m a

Initial state

-> (a -> Bni -> m a)

Folding function

-> FoldM m Bni a

Resulting FoldM

Create a FoldM from an initial state and a folding function operating in monadic context.

Since: 0.0.2.0

Utils

asPlainText :: NonEmpty Inline -> Text Source #

Convert a non-empty collection of Inlines into their plain text representation. This is used e.g. to render image descriptions.

headerId :: NonEmpty Inline -> Text Source #

Generate value of id attribute for a given header. This is used during rendering and also can be used to get id of a header for linking to it in extensions.

See also: headerFragment.

headerFragment :: Text -> URI Source #

Generate a URI containing only a fragment from its textual representation. Useful for getting URL from id of a header.