cmark-sections-0.3.0.1: Represent cmark-parsed Markdown as a tree of sections

Safe HaskellNone
LanguageHaskell2010

CMark.Sections

Contents

Description

This library lets you parse Markdown into a hierarchical structure (delimited by headings). For instance, let's say your document looks like this:

This is the preface.

First chapter
========================================

This chapter doesn't have sections.

Second chapter
========================================

First section
--------------------

Here's some text.

Second section
--------------------

And more text.

It can be represented as a tree:

preface: "This is the preface."

sections:
    * heading: "First chapter"
      content: "This chapter doesn't have sections."
      sections: []

    * heading: "Second chapter"
      sections:
          * heading: "First section"
            content: "Here's some text."
            sections: []

          * heading: "Second section"
            content: "And more text."
            sections: []

That's what this library does. Moreover, it lets you access the Markdown source of every node of the tree.

In most cases the only thing you need to do is something like this:

nodesToDocument . commonmarkToNodesWithSource [optSafe, optNormalize]

You can preprocess parsed Markdown after doing commonmarkToNodesWithSource as long as you don't add or remove any top-level nodes.

Synopsis

Parse Markdown to trees

commonmarkToNodesWithSource :: [CMarkOption] -> Text -> WithSource [Node] Source #

commonmarkToNodesWithSource parses Markdown with the given options and extracts nodes from the initial DOCUMENT node.

nodesToDocument :: WithSource [Node] -> Document () () Source #

Turn a list of Markdown nodes into a tree.

data WithSource a Source #

A data type for annotating things with their source. In this library we only use WithSource [Node], which stands for “some Markdown nodes + source”.

Constructors

WithSource Text a 
Instances
Functor WithSource Source # 
Instance details

Defined in CMark.Sections

Methods

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

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

Foldable WithSource Source # 
Instance details

Defined in CMark.Sections

Methods

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

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

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

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

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

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

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

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

toList :: WithSource a -> [a] #

null :: WithSource a -> Bool #

length :: WithSource a -> Int #

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

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

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

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

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

Traversable WithSource Source # 
Instance details

Defined in CMark.Sections

Methods

traverse :: Applicative f => (a -> f b) -> WithSource a -> f (WithSource b) #

sequenceA :: Applicative f => WithSource (f a) -> f (WithSource a) #

mapM :: Monad m => (a -> m b) -> WithSource a -> m (WithSource b) #

sequence :: Monad m => WithSource (m a) -> m (WithSource a) #

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

Defined in CMark.Sections

Methods

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

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

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

Defined in CMark.Sections

Methods

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

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

toConstr :: WithSource a -> Constr #

dataTypeOf :: WithSource a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in CMark.Sections

Generic (WithSource a) Source # 
Instance details

Defined in CMark.Sections

Associated Types

type Rep (WithSource a) :: * -> * #

Methods

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

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

Semigroup a => Semigroup (WithSource a) Source # 
Instance details

Defined in CMark.Sections

(Monoid a, Semigroup a) => Monoid (WithSource a) Source # 
Instance details

Defined in CMark.Sections

type Rep (WithSource a) Source # 
Instance details

Defined in CMark.Sections

type Rep (WithSource a) = D1 (MetaData "WithSource" "CMark.Sections" "cmark-sections-0.3.0.1-Bbogd1UD79eL1RVOfgh7et" False) (C1 (MetaCons "WithSource" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

getSource :: WithSource a -> Text Source #

Extract source from WithSource (it's stored there in a field).

stripSource :: WithSource a -> a Source #

Extract data from WithSource.

data Section a b Source #

A section in the Markdown tree.

Sections do not contain subsections; i.e. Section isn't recursive and the tree structure is provided by Data.Tree.

In a Section a b, the heading is coupled with a value of type a, and content – with a value of type b. This is occasionally useful.

Constructors

Section 

Fields

Instances
(Eq a, Eq b) => Eq (Section a b) Source # 
Instance details

Defined in CMark.Sections

Methods

(==) :: Section a b -> Section a b -> Bool #

(/=) :: Section a b -> Section a b -> Bool #

(Data a, Data b) => Data (Section a b) Source # 
Instance details

Defined in CMark.Sections

Methods

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

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

toConstr :: Section a b -> Constr #

dataTypeOf :: Section a b -> DataType #

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

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

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

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

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

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

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

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

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

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

(Show a, Show b) => Show (Section a b) Source # 
Instance details

Defined in CMark.Sections

Methods

showsPrec :: Int -> Section a b -> ShowS #

show :: Section a b -> String #

showList :: [Section a b] -> ShowS #

Generic (Section a b) Source # 
Instance details

Defined in CMark.Sections

Associated Types

type Rep (Section a b) :: * -> * #

Methods

from :: Section a b -> Rep (Section a b) x #

to :: Rep (Section a b) x -> Section a b #

type Rep (Section a b) Source # 
Instance details

Defined in CMark.Sections

data Document a b Source #

The whole parsed Markdown tree. In a Document a b, headings are annotated with a and content blocks – with b.

Constructors

Document 

Fields

Instances
(Eq b, Eq a) => Eq (Document a b) Source # 
Instance details

Defined in CMark.Sections

Methods

(==) :: Document a b -> Document a b -> Bool #

(/=) :: Document a b -> Document a b -> Bool #

(Data a, Data b) => Data (Document a b) Source # 
Instance details

Defined in CMark.Sections

Methods

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

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

toConstr :: Document a b -> Constr #

dataTypeOf :: Document a b -> DataType #

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

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

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

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

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

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

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

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

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

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

(Show b, Show a) => Show (Document a b) Source # 
Instance details

Defined in CMark.Sections

Methods

showsPrec :: Int -> Document a b -> ShowS #

show :: Document a b -> String #

showList :: [Document a b] -> ShowS #

Generic (Document a b) Source # 
Instance details

Defined in CMark.Sections

Associated Types

type Rep (Document a b) :: * -> * #

Methods

from :: Document a b -> Rep (Document a b) x #

to :: Rep (Document a b) x -> Document a b #

type Rep (Document a b) Source # 
Instance details

Defined in CMark.Sections

type Rep (Document a b) = D1 (MetaData "Document" "CMark.Sections" "cmark-sections-0.3.0.1-Bbogd1UD79eL1RVOfgh7et" False) (C1 (MetaCons "Document" PrefixI True) (S1 (MetaSel (Just "preface") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (WithSource [Node])) :*: (S1 (MetaSel (Just "prefaceAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b) :*: S1 (MetaSel (Just "sections") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Forest (Section a b))))))

Work with parsed trees

Note that you can use (<>) to combine WithSource nodes together. It will concatenate sources and parsed Markdown.

I'm not sure how valid this operation is for Markdown, but probably more-or-less valid (when you exclude corner cases like missing newlines at the end and duplicate links). Maybe cmark doesn't even allow duplicate links, I don't know.

flattenDocument :: Document a b -> WithSource [Node] Source #

Turn the whole parsed-and-broken-down Document into a list of nodes.

flattenSection :: Section a b -> WithSource [Node] Source #

Turn a section into a list of nodes.

flattenTree :: Tree (Section a b) -> WithSource [Node] Source #

Turn a Data.Tree Tree into a list of nodes.

flattenForest :: Forest (Section a b) -> WithSource [Node] Source #

Turn a Data.Tree Forest into a list of nodes.