Shared: define ordNub as alias for nubOrd from containers package (#7963)
This requires at least containers 0.6.0.1, which ships with the oldest GHC version currently supported by pandoc (GHC 8.6).
This commit is contained in:
parent
edfe34c86c
commit
1aeeba9ecb
2 changed files with 6 additions and 7 deletions
|
@ -472,7 +472,7 @@ library
|
|||
commonmark-extensions >= 0.2.3 && < 0.3,
|
||||
commonmark-pandoc >= 0.2.1.2 && < 0.3,
|
||||
connection >= 0.3.1,
|
||||
containers >= 0.4.2.1 && < 0.7,
|
||||
containers >= 0.6.0.1 && < 0.7,
|
||||
data-default >= 0.4 && < 0.8,
|
||||
deepseq >= 1.3 && < 1.5,
|
||||
directory >= 1.2.3 && < 1.4,
|
||||
|
|
|
@ -105,6 +105,7 @@ import qualified Data.Bifunctor as Bifunctor
|
|||
import Data.Char (isAlpha, isLower, isSpace, isUpper, toLower, isAlphaNum,
|
||||
generalCategory, GeneralCategory(NonSpacingMark,
|
||||
SpacingCombiningMark, EnclosingMark, ConnectorPunctuation))
|
||||
import Data.Containers.ListUtils (nubOrd)
|
||||
import Data.List (find, intercalate, intersperse, sortOn, foldl')
|
||||
import qualified Data.Map as M
|
||||
import Data.Maybe (mapMaybe, fromMaybe)
|
||||
|
@ -174,14 +175,12 @@ splitAt' n xs | n <= 0 = ([],xs)
|
|||
splitAt' n (x:xs) = (x:ys,zs)
|
||||
where (ys,zs) = splitAt' (n - charWidth x) xs
|
||||
|
||||
-- | Remove duplicates from a list.
|
||||
ordNub :: (Ord a) => [a] -> [a]
|
||||
ordNub l = go Set.empty l
|
||||
where
|
||||
go _ [] = []
|
||||
go s (x:xs) = if x `Set.member` s then go s xs
|
||||
else x : go (Set.insert x s) xs
|
||||
ordNub = nubOrd
|
||||
{-# INLINE ordNub #-}
|
||||
|
||||
-- | Returns the last element in a foldable structure for that the
|
||||
-- | Returns the first element in a foldable structure for that the
|
||||
-- monadic predicate holds true, and @Nothing@ if no such element
|
||||
-- exists.
|
||||
findM :: forall m t a. (Monad m, Foldable t)
|
||||
|
|
Loading…
Reference in a new issue