commonmark-0.2.6: Pure Haskell commonmark parser.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Commonmark.Types

Contents

Synopsis

Documentation

newtype Format Source #

Constructors

Format Text 

Instances

Instances details
Data Format Source # 
Instance details

Defined in Commonmark.Types

Methods

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

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

toConstr :: Format -> Constr #

dataTypeOf :: Format -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Format Source # 
Instance details

Defined in Commonmark.Types

Eq Format Source # 
Instance details

Defined in Commonmark.Types

Methods

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

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

data ListSpacing Source #

Constructors

TightList 
LooseList 

Instances

Instances details
Data ListSpacing Source # 
Instance details

Defined in Commonmark.Types

Methods

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

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

toConstr :: ListSpacing -> Constr #

dataTypeOf :: ListSpacing -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListSpacing Source # 
Instance details

Defined in Commonmark.Types

Eq ListSpacing Source # 
Instance details

Defined in Commonmark.Types

Ord ListSpacing Source # 
Instance details

Defined in Commonmark.Types

data ListType Source #

Instances

Instances details
Data ListType Source # 
Instance details

Defined in Commonmark.Types

Methods

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

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

toConstr :: ListType -> Constr #

dataTypeOf :: ListType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListType Source # 
Instance details

Defined in Commonmark.Types

Eq ListType Source # 
Instance details

Defined in Commonmark.Types

Ord ListType Source # 
Instance details

Defined in Commonmark.Types

data DelimiterType Source #

Constructors

Period 
OneParen 
TwoParens 

Instances

Instances details
Data DelimiterType Source # 
Instance details

Defined in Commonmark.Types

Methods

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

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

toConstr :: DelimiterType -> Constr #

dataTypeOf :: DelimiterType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DelimiterType Source # 
Instance details

Defined in Commonmark.Types

Eq DelimiterType Source # 
Instance details

Defined in Commonmark.Types

Ord DelimiterType Source # 
Instance details

Defined in Commonmark.Types

data EnumeratorType Source #

Instances

Instances details
Data EnumeratorType Source # 
Instance details

Defined in Commonmark.Types

Methods

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

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

toConstr :: EnumeratorType -> Constr #

dataTypeOf :: EnumeratorType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show EnumeratorType Source # 
Instance details

Defined in Commonmark.Types

Eq EnumeratorType Source # 
Instance details

Defined in Commonmark.Types

Ord EnumeratorType Source # 
Instance details

Defined in Commonmark.Types

class (Monoid a, Show a, Rangeable a, HasAttributes a) => IsInline a where Source #

Methods

lineBreak :: a Source #

softBreak :: a Source #

str :: Text -> a Source #

entity :: Text -> a Source #

escapedChar :: Char -> a Source #

emph :: a -> a Source #

strong :: a -> a Source #

link Source #

Arguments

:: Text

Destination

-> Text

Title

-> a

Link description

-> a 

image Source #

Arguments

:: Text

Source

-> Text

Title

-> a

Description

-> a 

code :: Text -> a Source #

rawInline :: Format -> Text -> a Source #

class (Monoid b, Show b, Rangeable b, IsInline il, HasAttributes b) => IsBlock il b | b -> il where Source #

Methods

paragraph :: il -> b Source #

plain :: il -> b Source #

thematicBreak :: b Source #

blockQuote :: b -> b Source #

codeBlock :: Text -> Text -> b Source #

heading Source #

Arguments

:: Int

Level

-> il

text

-> b 

rawBlock :: Format -> Text -> b Source #

referenceLinkDefinition Source #

Arguments

:: Text

Label

-> (Text, Text)

Destination, title

-> b 

list :: ListType -> ListSpacing -> [b] -> b Source #

newtype SourceRange Source #

Constructors

SourceRange 

Instances

Instances details
Data SourceRange Source # 
Instance details

Defined in Commonmark.Types

Methods

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

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

toConstr :: SourceRange -> Constr #

dataTypeOf :: SourceRange -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid SourceRange Source # 
Instance details

Defined in Commonmark.Types

Semigroup SourceRange Source # 
Instance details

Defined in Commonmark.Types

Show SourceRange Source # 
Instance details

Defined in Commonmark.Types

Eq SourceRange Source # 
Instance details

Defined in Commonmark.Types

Ord SourceRange Source # 
Instance details

Defined in Commonmark.Types

Rangeable (Html SourceRange) Source # 
Instance details

Defined in Commonmark.Html

class Rangeable a where Source #

Methods

ranged :: SourceRange -> a -> a Source #

Instances

Instances details
Rangeable (Html SourceRange) Source # 
Instance details

Defined in Commonmark.Html

Rangeable (Html ()) Source # 
Instance details

Defined in Commonmark.Html

Methods

ranged :: SourceRange -> Html () -> Html () Source #

(Rangeable a, Monoid a, Show a) => Rangeable (WithSourceMap a) Source # 
Instance details

Defined in Commonmark.SourceMap

class HasAttributes a where Source #

Methods

addAttributes :: Attributes -> a -> a Source #

Instances

Instances details
HasAttributes (Html a) Source # 
Instance details

Defined in Commonmark.Html

HasAttributes (WithSourceMap a) Source # 
Instance details

Defined in Commonmark.SourceMap

class ToPlainText a where Source #

Methods

toPlainText :: a -> Text Source #

Instances

Instances details
ToPlainText (Html a) Source # 
Instance details

Defined in Commonmark.Html

Methods

toPlainText :: Html a -> Text Source #

ToPlainText a => ToPlainText (WithSourceMap a) Source # 
Instance details

Defined in Commonmark.SourceMap

Re-exports

data SourcePos #

The abstract data type SourcePos represents source positions. It contains the name of the source (i.e. file name), a line number and a column number. SourcePos is an instance of the Show, Eq and Ord class.

Instances

Instances details
Data SourcePos 
Instance details

Defined in Text.Parsec.Pos

Methods

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

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

toConstr :: SourcePos -> Constr #

dataTypeOf :: SourcePos -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SourcePos 
Instance details

Defined in Text.Parsec.Pos

Eq SourcePos 
Instance details

Defined in Text.Parsec.Pos

Ord SourcePos 
Instance details

Defined in Text.Parsec.Pos

sourceLine :: SourcePos -> Line #

Extracts the line number from a source position.

sourceColumn :: SourcePos -> Column #

Extracts the column number from a source position.

sourceName :: SourcePos -> SourceName #

Extracts the name of the source from a source position.