T.P.Shared: remove some obsolete functions [API change].

Removed:

- `splitByIndices`
- `splitStringByIndicies`
- `substitute`
- `underlineSpan`

None of these are used elsewhere in the code base.
This commit is contained in:
John MacFarlane 2021-02-20 23:01:07 -08:00
parent 321343b2cf
commit d8ef383692

View file

@ -21,10 +21,7 @@ module Text.Pandoc.Shared (
-- * List processing -- * List processing
splitBy, splitBy,
splitTextBy, splitTextBy,
splitByIndices,
splitStringByIndices,
splitTextByIndices, splitTextByIndices,
substitute,
ordNub, ordNub,
findM, findM,
-- * Text processing -- * Text processing
@ -74,7 +71,6 @@ module Text.Pandoc.Shared (
addMetaField, addMetaField,
makeMeta, makeMeta,
eastAsianLineBreakFilter, eastAsianLineBreakFilter,
underlineSpan,
htmlSpanLikeElements, htmlSpanLikeElements,
splitSentences, splitSentences,
filterIpynbOutput, filterIpynbOutput,
@ -113,7 +109,7 @@ import qualified Data.Bifunctor as Bifunctor
import Data.Char (isAlpha, isLower, isSpace, isUpper, toLower, isAlphaNum, import Data.Char (isAlpha, isLower, isSpace, isUpper, toLower, isAlphaNum,
generalCategory, GeneralCategory(NonSpacingMark, generalCategory, GeneralCategory(NonSpacingMark,
SpacingCombiningMark, EnclosingMark, ConnectorPunctuation)) SpacingCombiningMark, EnclosingMark, ConnectorPunctuation))
import Data.List (find, intercalate, intersperse, stripPrefix, sortOn) import Data.List (find, intercalate, intersperse, sortOn)
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe (mapMaybe, fromMaybe) import Data.Maybe (mapMaybe, fromMaybe)
import Data.Monoid (Any (..)) import Data.Monoid (Any (..))
@ -160,27 +156,6 @@ splitTextBy isSep t
| otherwise = let (first, rest) = T.break isSep t | otherwise = let (first, rest) = T.break isSep t
in first : splitTextBy isSep (T.dropWhile isSep rest) in first : splitTextBy isSep (T.dropWhile isSep rest)
{-# DEPRECATED splitByIndices "This function is slated for removal" #-}
splitByIndices :: [Int] -> [a] -> [[a]]
splitByIndices [] lst = [lst]
splitByIndices (x:xs) lst = first:splitByIndices (map (\y -> y - x) xs) rest
where (first, rest) = splitAt x lst
{-# DEPRECATED splitStringByIndices "This function is slated for removal" #-}
-- | Split string into chunks divided at specified indices.
splitStringByIndices :: [Int] -> [Char] -> [[Char]]
splitStringByIndices [] lst = [lst]
splitStringByIndices (x:xs) lst =
let (first, rest) = splitAt' x lst in
first : splitStringByIndices (map (\y -> y - x) xs) rest
-- DEPRECATED: can be removed when splitStringByIndices is
splitAt' :: Int -> [Char] -> ([Char],[Char])
splitAt' _ [] = ([],[])
splitAt' n xs | n <= 0 = ([],xs)
splitAt' n (x:xs) = (x:ys,zs)
where (ys,zs) = splitAt' (n - charWidth x) xs
splitTextByIndices :: [Int] -> T.Text -> [T.Text] splitTextByIndices :: [Int] -> T.Text -> [T.Text]
splitTextByIndices ns = splitTextByRelIndices (zipWith (-) ns (0:ns)) splitTextByIndices ns = splitTextByRelIndices (zipWith (-) ns (0:ns))
where where
@ -189,16 +164,6 @@ splitTextByIndices ns = splitTextByRelIndices (zipWith (-) ns (0:ns))
let (first, rest) = T.splitAt x t let (first, rest) = T.splitAt x t
in first : splitTextByRelIndices xs rest in first : splitTextByRelIndices xs rest
{-# DEPRECATED substitute "This function is slated for removal" #-}
-- | Replace each occurrence of one sublist in a list with another.
substitute :: (Eq a) => [a] -> [a] -> [a] -> [a]
substitute _ _ [] = []
substitute [] _ xs = xs
substitute target replacement lst@(x:xs) =
case stripPrefix target lst of
Just lst' -> replacement ++ substitute target replacement lst'
Nothing -> x : substitute target replacement xs
ordNub :: (Ord a) => [a] -> [a] ordNub :: (Ord a) => [a] -> [a]
ordNub l = go Set.empty l ordNub l = go Set.empty l
where where
@ -765,13 +730,6 @@ eastAsianLineBreakFilter = bottomUp go
go xs go xs
= xs = xs
{-# DEPRECATED underlineSpan "Use Text.Pandoc.Builder.underline instead" #-}
-- | Builder for underline (deprecated).
-- This probably belongs in Builder.hs in pandoc-types.
-- Will be replaced once Underline is an element.
underlineSpan :: Inlines -> Inlines
underlineSpan = B.underline
-- | Set of HTML elements that are represented as Span with a class equal as -- | Set of HTML elements that are represented as Span with a class equal as
-- the element tag itself. -- the element tag itself.
htmlSpanLikeElements :: Set.Set T.Text htmlSpanLikeElements :: Set.Set T.Text