mmark-ext-0.0.1.1: Commonly useful extensions for MMark markdown processor

Copyright© 2017 Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.MMark.Extension.Common

Contents

Description

Commonly useful extensions for MMark markdown processor.

We suggest using a qualified import, like this:

import qualified Text.MMark.Extension.Common as Ext

Here is an example that uses several extensions from this module at the same time, it should give you an idea where to start:

{-# LANGUAGE OverloadedStrings #-}

module Main (main) where

import Data.Default.Class
import qualified Data.Text.IO                as T
import qualified Data.Text.Lazy.IO           as TL
import qualified Lucid                       as L
import qualified Text.MMark                  as MMark
import qualified Text.MMark.Extension.Common as Ext

main :: IO ()
main = do
  let input = "input.md"
  txt <- T.readFile input
  case MMark.parse input txt of
    Left errs -> putStrLn (MMark.parseErrorsPretty txt errs)
    Right r ->
      let toc = MMark.runScanner r (Ext.tocScanner 4)
      in TL.writeFile "output.html"
          . L.renderText
          . MMark.render
          . MMark.useExtensions
              [ Ext.toc "toc" toc
              , Ext.punctuationPrettifier def
              , Ext.obfuscateEmail "protected-email"
              , Ext.fontAwesome ]
          $ r

Synopsis

Table of contents

Place this markup in markdown document where you want table of contents to be inserted:

```toc
```

You may use something different than "toc" as the info string of the code block.

data Toc Source #

An opaque type representing table of contents produced by the tocScanner scanner.

tocScanner Source #

Arguments

:: Int

Up to which level (inclusive) to collect headers? Values from 2 to 6 make sense here.

-> Fold Bni Toc 

The scanner builds table of contents Toc that can then be passed to toc to obtain an extension that renders the table of contents in HTML.

Note: Top level header (level 1) is never added to the table of contents. Open an issue if you think it's not a good behavior.

toc Source #

Arguments

:: Text

Label of the code block to replace by the table of contents

-> Toc

Previously generated by tocScanner

-> Extension 

Create an extension that replaces a certain code block with previously constructed table of contents.

Punctuation prettifier

data Punctuation Source #

Settings for the punctuation-prettifying extension.

Constructors

Punctuation 

Fields

Instances

Eq Punctuation Source # 
Data Punctuation Source # 

Methods

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

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

toConstr :: Punctuation -> Constr #

dataTypeOf :: Punctuation -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Punctuation Source # 
Read Punctuation Source # 
Show Punctuation Source # 
Generic Punctuation Source # 

Associated Types

type Rep Punctuation :: * -> * #

Default Punctuation Source # 

Methods

def :: Punctuation #

type Rep Punctuation Source # 
type Rep Punctuation = D1 (MetaData "Punctuation" "Text.MMark.Extension.Common" "mmark-ext-0.0.1.1-3yux9wFyWh41hhLRmbe8o" False) (C1 (MetaCons "Punctuation" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "punctEnDash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "punctEmDash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))))

punctuationPrettifier :: Punctuation -> Extension Source #

Prettify punctuation according to the settings in Punctuation.

Email address obfuscation

obfuscateEmail Source #

Arguments

:: Text

Name of class to assign to the links, e.g. "protected-email"

-> Extension 

This extension makes email addresses in links be rendered as something like this:

<a class="protected-email"
   data-email="something@example.org"
   href="javascript:void(0)">Enable JavaScript to see the email</a>

You'll also need to include jQuery and this bit of JS code for the magic to work:

$(document).ready(function () {
    $(".protected-email").each(function () {
        var item = $(this);
        var email = item.data('email');
        item.attr('href', 'mailto:' + email);
        item.html(email);
    });
});

Font Awesome icons

fontAwesome :: Extension Source #

Allow to insert spans with font awesome icons using autolinks like this:

<fa:user>

This user identifier is the name of icon you want to insert. You can also control the size of the icon like this:

<fa:user/fw> -- fixed width
<fa:user/lg> -- large
<fa:user/2x>
<fa:user/3x>
<fa:user/4x>
<fa:user/5x>

In general, all path components in this URI that go after the name of icon will be prefixed with "fa-" and added as classes, so you can do a lot of fancy stuff, see http://fontawesome.io/examples/:

<fa:quote-left/3x/pull-left/border>

See also: http://fontawesome.io.