Add Text.Pandoc.Shared.ToString typeclass (API change)

This commit is contained in:
Alexander Krotov 2018-11-01 14:09:11 +03:00 committed by John MacFarlane
parent 418bd42df8
commit 95eccb94b0

View file

@ -6,6 +6,8 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-
Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
@ -43,6 +45,7 @@ module Text.Pandoc.Shared (
substitute,
ordNub,
-- * Text processing
ToString (..),
backslashEscapes,
escapeStringUsing,
stripTrailingNewlines,
@ -193,6 +196,15 @@ ordNub l = go Set.empty l
-- Text processing
--
class ToString a where
toString :: a -> String
instance ToString String where
toString = id
instance ToString T.Text where
toString = T.unpack
-- | Returns an association list of backslash escapes for the
-- designated characters.
backslashEscapes :: [Char] -- ^ list of special characters to escape