{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} module Commonmark.Extensions.Superscript ( HasSuperscript(..) , superscriptSpec ) where import Commonmark.Types import Commonmark.Syntax import Commonmark.Inlines import Commonmark.SourceMap import Commonmark.Html superscriptSpec :: (Monad m, IsBlock il bl, IsInline il, HasSuperscript il) => SyntaxSpec m il bl superscriptSpec :: forall (m :: * -> *) il bl. (Monad m, IsBlock il bl, IsInline il, HasSuperscript il) => SyntaxSpec m il bl superscriptSpec = SyntaxSpec m il bl forall a. Monoid a => a mempty { syntaxFormattingSpecs = [ FormattingSpec '^' True True (Just superscript) Nothing '^' ] } class HasSuperscript a where superscript :: a -> a instance HasSuperscript (Html a) where superscript :: Html a -> Html a superscript Html a x = Text -> Maybe (Html a) -> Html a forall a. Text -> Maybe (Html a) -> Html a htmlInline Text "sup" (Html a -> Maybe (Html a) forall a. a -> Maybe a Just Html a x) instance (HasSuperscript i, Monoid i) => HasSuperscript (WithSourceMap i) where superscript :: WithSourceMap i -> WithSourceMap i superscript WithSourceMap i x = (i -> i forall a. HasSuperscript a => a -> a superscript (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 "superscript"