{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} module Commonmark.Extensions.HardLineBreaks ( hardLineBreaksSpec ) where import Commonmark.Types import Commonmark.Syntax import Commonmark.Inlines import Commonmark.TokParsers import Commonmark.Tokens hardLineBreaksSpec :: (Monad m, IsBlock il bl, IsInline il) => SyntaxSpec m il bl hardLineBreaksSpec :: forall (m :: * -> *) il bl. (Monad m, IsBlock il bl, IsInline il) => SyntaxSpec m il bl hardLineBreaksSpec = SyntaxSpec m il bl forall a. Monoid a => a mempty { syntaxInlineParsers = [ hardLineBreakParser ] } hardLineBreakParser :: (Monad m, IsInline a) => InlineParser m a hardLineBreakParser :: forall (m :: * -> *) a. (Monad m, IsInline a) => InlineParser m a hardLineBreakParser = a forall a. IsInline a => a lineBreak a -> ParsecT [Tok] (IPState m) (StateT Enders m) Tok -> ParsecT [Tok] (IPState m) (StateT Enders m) a forall a b. a -> ParsecT [Tok] (IPState m) (StateT Enders m) b -> ParsecT [Tok] (IPState m) (StateT Enders m) a forall (f :: * -> *) a b. Functor f => a -> f b -> f a <$ (Tok -> Bool) -> ParsecT [Tok] (IPState m) (StateT Enders m) Tok forall (m :: * -> *) s. Monad m => (Tok -> Bool) -> ParsecT [Tok] s m Tok satisfyTok (TokType -> Tok -> Bool hasType TokType LineEnd)