{- Copyright (C) 2010 Dr. Alistair Ward This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} {- | [@AUTHOR@] Dr. Alistair Ward [@DESCRIPTION@] Miscellaneous polymorphic list-operations. -} module ToolShed.ListPlus( -- * Types -- ** Type-synonyms ChunkLength, -- Split, -- * Functions chunk, excise, groupComparing, linearise, merge, mergeBy, -- splitsFrom, splitsLeftFrom, splitsRightFrom, takeUntil ) where import qualified Control.Arrow import qualified Data.List -- | The length of the chunks into which a list is split. type ChunkLength = Int {- | * Splits a list into length-@size@ pieces, where @(size >= 0)@. * The last chunk will be shorter, if @n@ isn't an aliquot part of the input list-length. * If @(size == 0)@, the resulting list will be an infinite sequence of null lists. * CAVEAT: a similar function is available in the module /Data.List.Split/, though this one checks for @(size < 0)@. -} chunk :: ChunkLength -> [a] -- ^ The polymorphic input list to be chunked. -> [[a]] chunk size list | size < 0 = error $ "ToolShed.ListPlus.chunk:\tnegative chunk-size=" ++ show size | otherwise = chunk' list where chunk' :: [a] -> [[a]] chunk' [] = [] chunk' a = uncurry (:) . Control.Arrow.second chunk' $ splitAt size a -- | Remove the single indexed element from the list. excise :: Int -- ^ The index. -> [a] -- ^ The polymorphic input list. -> [a] -- ^ The same list, with the indexed element removed. excise 0 = tail --Just for efficiency. excise i = uncurry (++) . Control.Arrow.second tail . splitAt i {- | * Much like 'Data.List.GroupBy', but where the normal binary predicate, is composed from equality, after the same unary translation-function has been applied to both list-elements. * cf. 'GHC.Exts.groupWith', which uses the function parameter to both sort and group. -} groupComparing :: Eq b => (a -> b) -- ^ Translates elements from the list, prior to testing the translated values for equality. -> [a] -- ^ The polymorphic input list to group. -> [[a]] -- ^ The same list split into chunks of the required length. groupComparing f = Data.List.groupBy (\a b -> f a == f b) -- | Converts a list of /Pairs/, into a narrower list. linearise :: [(a, a)] -> [a] linearise [] = [] linearise ((l, r) : remainder) = l : r : linearise remainder --Recurse {- | * Merge two sorted lists, to product a single sorted list. * The merge-process is /stable/, in that where items from each list are equal, they remain in the original order. -} merge :: Ord a => [a] -> [a] -> [a] merge [] r = r merge l [] = l merge l@(x : xs) r@(y : ys) | x > y = y : merge l ys | otherwise = x : merge xs r {- | * Merge two sorted lists, according to the specified order, to product a single sorted list. * The merge-process is /stable/, in that where items from each list are equal, they remain in the original order. -} mergeBy :: Ord a => (a -> a -> Ordering) -> [a] -> [a] -> [a] mergeBy _ [] r = r mergeBy _ l [] = l mergeBy cmp l@(x : xs) r@(y : ys) | x `cmp` y == GT = y : mergeBy cmp l ys | otherwise = x : mergeBy cmp xs r -- | The polymorphic pair, resulting from splitting a list of arbitrary type. type Split a = ([a] {-left list-}, [a] {-right list-}) -- | Use the specified transformation, to generate a list of 'Split's, from the initial one. splitsFrom :: (Split a -> Split a) -- ^ The function used to transform one /split/ into the next. -> Int -- ^ Index. -> [a] -- ^ The polymorphic input list from which the /splits/ are generated. -> [Split a] -- ^ The list of all required splits of the single input list. splitsFrom transformation i = iterate transformation . splitAt i {- | * Create the set of all 'Split's, migrating left from the specified location. * CAVEAT: 'init' fails when 'fst' has been reduced to null. -} splitsLeftFrom :: Int -- ^ Index. -> [a] -- ^ The polymorphic input list from which the /splits/ are generated, as the index is stepped left -> [Split a] -- ^ The list of all required splits of the single input list. splitsLeftFrom start | start < 0 = error $ "ToolShed.ListPlus.splitsLeftFrom:\tnegative starting-index; " ++ show start | otherwise = splitsFrom (\(l, r) -> (init l, last l : r)) start {- | * Create the set of all 'Split's, migrating right from the specified location. * CAVEAT: pattern-match against @ : @ fails, when 'snd' has been reduced to null. -} splitsRightFrom :: Int -- ^ Index. -> [a] -- ^ The polymorphic input list from which the /splits/ are generated, as the index is stepped right. -> [Split a] -- ^ The list of all required splits of the single input list. splitsRightFrom start | start < 0 = error $ "ToolShed.ListPlus.splitsRightFrom:\tnegative starting-index; " ++ show start | otherwise = splitsFrom (\(l, r : rs) -> (l ++ [r], rs)) start {- | * Take until the specified predicate is satisfied; /including/ the item which satisfied it. * NB: @takeWhile (not . test)@ would return one fewer item. -} takeUntil :: (a -> Bool) -- ^ Predicate, used to determine the last item taken. -> [a] -- ^ The polymorphic input list. -> [a] takeUntil predicate = takeUntil' where takeUntil' (x : xs) = x {-take regardless-} : if predicate x then [] else takeUntil' xs takeUntil' _ = []