{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} module Commonmark.Extensions.Strikethrough ( HasStrikethrough(..) , strikethroughSpec ) where import Commonmark.Types import Commonmark.Syntax import Commonmark.Inlines import Commonmark.SourceMap import Commonmark.Html strikethroughSpec :: (Monad m, IsBlock il bl, IsInline il, HasStrikethrough il) => SyntaxSpec m il bl strikethroughSpec :: forall (m :: * -> *) il bl. (Monad m, IsBlock il bl, IsInline il, HasStrikethrough il) => SyntaxSpec m il bl strikethroughSpec = SyntaxSpec m il bl forall a. Monoid a => a mempty { syntaxFormattingSpecs = [ FormattingSpec '~' True True Nothing (Just strikethrough) '~' ] } class HasStrikethrough a where strikethrough :: a -> a instance HasStrikethrough (Html a) where strikethrough :: Html a -> Html a strikethrough Html a x = Text -> Maybe (Html a) -> Html a forall a. Text -> Maybe (Html a) -> Html a htmlInline Text "del" (Html a -> Maybe (Html a) forall a. a -> Maybe a Just Html a x) instance (HasStrikethrough i, Monoid i) => HasStrikethrough (WithSourceMap i) where strikethrough :: WithSourceMap i -> WithSourceMap i strikethrough WithSourceMap i x = (i -> i forall a. HasStrikethrough a => a -> a strikethrough (i -> i) -> WithSourceMap i -> WithSourceMap i forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> WithSourceMap i x) WithSourceMap i -> WithSourceMap () -> WithSourceMap i forall a b. WithSourceMap a -> WithSourceMap b -> WithSourceMap a forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a <* Text -> WithSourceMap () addName Text "strikethrough"