@@ -54,6 +54,7 @@ import Data.List (isInfixOf)
5454import Data.Maybe
5555import Data.Text (Text )
5656import qualified Data.Text as T
57+ import Safe (lastMay )
5758import Text.Pandoc.Builder (Blocks , Inlines , fromList , toList , trimInlines )
5859import qualified Text.Pandoc.Builder as B (blockQuote , bulletList , code ,
5960 codeBlockWith , definitionList ,
@@ -510,9 +511,7 @@ strong = try $ do
510511 notFollowedBy (oneOf spaceChars)
511512 contents <- mconcat <$> many1Till inline'
512513 (try (char ' *' *> notFollowedBy alphaNum))
513- guard $ case reverse (toList contents) of
514- Space : _ -> False
515- _ -> True
514+ guard $ lastMay (toList contents) /= Just Space
516515 return $ B. spanWith (makeId contents, [] , [] ) mempty <> B. strong contents
517516
518517makeId :: Inlines -> Text
@@ -524,9 +523,7 @@ emph = try $ do
524523 notFollowedBy (oneOf spaceChars)
525524 contents <- mconcat <$> many1Till inline'
526525 (try (char ' _' *> notFollowedBy alphaNum))
527- guard $ case reverse (toList contents) of
528- Space : _ -> False
529- _ -> True
526+ guard $ lastMay (toList contents) /= Just Space
530527 return $ B. emph contents
531528
532529strikeout :: PandocMonad m => VwParser m Inlines
0 commit comments