Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Format = Format Text
- data ListSpacing
- data ListType
- data DelimiterType
- data EnumeratorType
- class (Monoid a, Show a, Rangeable a, HasAttributes a) => IsInline a where
- class (Monoid b, Show b, Rangeable b, IsInline il, HasAttributes b) => IsBlock il b | b -> il where
- paragraph :: il -> b
- plain :: il -> b
- thematicBreak :: b
- blockQuote :: b -> b
- codeBlock :: Text -> Text -> b
- heading :: Int -> il -> b
- rawBlock :: Format -> Text -> b
- referenceLinkDefinition :: Text -> (Text, Text) -> b
- list :: ListType -> ListSpacing -> [b] -> b
- newtype SourceRange = SourceRange {
- unSourceRange :: [(SourcePos, SourcePos)]
- data SourcePos
- class Rangeable a where
- ranged :: SourceRange -> a -> a
- type Attribute = (Text, Text)
- type Attributes = [Attribute]
- class HasAttributes a where
- addAttributes :: Attributes -> a -> a
- class ToPlainText a where
- toPlainText :: a -> Text
Documentation
Instances
Eq Format Source # | |
Data Format Source # | |
Defined in Commonmark.Types 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 # | |
data ListSpacing Source #
Instances
Instances
Eq ListType Source # | |
Data ListType Source # | |
Defined in Commonmark.Types 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 # | |
Ord ListType Source # | |
Defined in Commonmark.Types | |
Show ListType Source # | |
data DelimiterType Source #
Instances
data EnumeratorType Source #
Instances
class (Monoid a, Show a, Rangeable a, HasAttributes a) => IsInline a where Source #
escapedChar :: Char -> a Source #
Instances
(IsInline a, Semigroup a) => IsInline (WithSourceMap a) Source # | |
Defined in Commonmark.SourceMap lineBreak :: WithSourceMap a Source # softBreak :: WithSourceMap a Source # str :: Text -> WithSourceMap a Source # entity :: Text -> WithSourceMap a Source # escapedChar :: Char -> WithSourceMap a Source # emph :: WithSourceMap a -> WithSourceMap a Source # strong :: WithSourceMap a -> WithSourceMap a Source # link :: Text -> Text -> WithSourceMap a -> WithSourceMap a Source # image :: Text -> Text -> WithSourceMap a -> WithSourceMap a Source # code :: Text -> WithSourceMap a Source # | |
Rangeable (Html a) => IsInline (Html a) Source # | |
Defined in Commonmark.Html |
class (Monoid b, Show b, Rangeable b, IsInline il, HasAttributes b) => IsBlock il b | b -> il where Source #
thematicBreak :: b Source #
blockQuote :: b -> b Source #
codeBlock :: Text -> Text -> b Source #
:: Int | Level |
-> il | text |
-> b |
rawBlock :: Format -> Text -> b Source #
referenceLinkDefinition Source #
list :: ListType -> ListSpacing -> [b] -> b Source #
Instances
newtype SourceRange Source #
SourceRange | |
|
Instances
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
Eq SourcePos | |
Data SourcePos | |
Defined in Text.Parsec.Pos 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 # | |
Ord SourcePos | |
Defined in Text.Parsec.Pos | |
Show SourcePos | |
class Rangeable a where Source #
ranged :: SourceRange -> a -> a Source #
Instances
(Rangeable a, Monoid a, Show a) => Rangeable (WithSourceMap a) Source # | |
Defined in Commonmark.SourceMap ranged :: SourceRange -> WithSourceMap a -> WithSourceMap a Source # | |
Rangeable (Html ()) Source # | |
Defined in Commonmark.Html | |
Rangeable (Html SourceRange) Source # | |
Defined in Commonmark.Html ranged :: SourceRange -> Html SourceRange -> Html SourceRange Source # |
type Attributes = [Attribute] Source #
class HasAttributes a where Source #
addAttributes :: Attributes -> a -> a Source #
Instances
HasAttributes (WithSourceMap a) Source # | |
Defined in Commonmark.SourceMap addAttributes :: Attributes -> WithSourceMap a -> WithSourceMap a Source # | |
HasAttributes (Html a) Source # | |
Defined in Commonmark.Html addAttributes :: Attributes -> Html a -> Html a Source # |
class ToPlainText a where Source #
toPlainText :: a -> Text Source #
Instances
ToPlainText a => ToPlainText (WithSourceMap a) Source # | |
Defined in Commonmark.SourceMap toPlainText :: WithSourceMap a -> Text Source # | |
ToPlainText (Html a) Source # | |
Defined in Commonmark.Html toPlainText :: Html a -> Text Source # |