commonmark-wikilink-0.1.0.0: Obsidian-friendly commonmark wikilink parser
Safe HaskellSafe-Inferred
LanguageHaskell2010

Commonmark.Extensions.WikiLink

Synopsis

Types

data WikiLink Source #

Represents the Foo in [[Foo]]

As wiki links may contain multiple path components, it can represent [[Foo/Bar]], hence we use nonempty slug list.

Instances

data WikiLinkType Source #

A # prefix or suffix allows semantically distinct wikilinks

Typically called branching link or a tag link, when used with #.

Constructors

WikiLinkNormal
[Foo
]
WikiLinkBranch
[Foo
]#
WikiLinkTag

#[[Foo]]

WikiLinkEmbed

![[Foo]]

Instances

Instances details
ToJSON WikiLinkType Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

Data WikiLinkType Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

Methods

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

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

toConstr :: WikiLinkType -> Constr #

dataTypeOf :: WikiLinkType -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded WikiLinkType Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

Enum WikiLinkType Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

Generic WikiLinkType Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

Associated Types

type Rep WikiLinkType :: Type -> Type #

Read WikiLinkType Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

Show WikiLinkType Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

Eq WikiLinkType Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

Ord WikiLinkType Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

type Rep WikiLinkType Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

type Rep WikiLinkType = D1 ('MetaData "WikiLinkType" "Commonmark.Extensions.WikiLink" "commonmark-wikilink-0.1.0.0-4wH84OHkupYLK40EJAas0G" 'False) ((C1 ('MetaCons "WikiLinkNormal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WikiLinkBranch" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WikiLinkTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WikiLinkEmbed" 'PrefixI 'False) (U1 :: Type -> Type)))

Parsing wikilinks

delineateLink :: [(Text, Text)] -> Text -> Maybe (Either (WikiLinkType, WikiLink) FilePath, Maybe Anchor) Source #

Given a Pandoc Link node, apparaise what kind of link it is.

  • Nothing, if the link is an absolute URL
  • Just (Left wl), if a wiki-link
  • Just (Right fp), if a relative path (not a wiki-link)

Wikilink candidates

allowedWikiLinks :: HasCallStack => NonEmpty Slug -> NonEmpty (WikiLinkType, WikiLink) Source #

Return the various ways to link to a route (ignoring ext)

FooBarQux.md -> [[Qux]], [[BarQux]], [[FooBar/Qux]]

All possible combinations of Wikilink type use is automatically included.

Converting wikilinks

Commonmark parser spec

wikilinkSpec :: (Monad m, IsInline il, HasWikiLink il) => SyntaxSpec m il bl Source #

Like wikilinkSpec but Zettelkasten-friendly.

Compared with the official extension, this has two differences:

  • Supports flipped inner text, eg: `[[Foo | some inner text]]`
  • Supports neuron folgezettel, i.e.: #[[Foo]] or [[Foo]]#

Anchors in URLs

data Anchor Source #

An URL anchor without the #

Instances

Instances details
Show Anchor Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

Eq Anchor Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

Methods

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

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

Ord Anchor Source # 
Instance details

Defined in Commonmark.Extensions.WikiLink

Pandoc helper

plainify :: [Inline] -> Text Source #

Convert Pandoc AST inlines to raw text.

TODO: extend on top of plainify from heist-extra