-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Combinator library for splitting lists. -- -- Combinator library and utility functions for splitting lists. @package split @version 0.1.1 -- | Implementation module for Data.List.Split, a combinator library -- for splitting lists. See the Data.List.Split documentation for -- more description and examples. module Data.List.Split.Internals -- | A splitting strategy. data Splitter a Splitter :: Delimiter a -> DelimPolicy -> CondensePolicy -> EndPolicy -> EndPolicy -> Splitter a -- | What delimiter to split on delimiter :: Splitter a -> Delimiter a -- | What to do with delimiters (drop from output, keep as separate -- elements in output, or merge with previous or following chunks) delimPolicy :: Splitter a -> DelimPolicy -- | What to do with multiple consecutive delimiters condensePolicy :: Splitter a -> CondensePolicy -- | Drop an initial blank? initBlankPolicy :: Splitter a -> EndPolicy -- | Drop a final blank? finalBlankPolicy :: Splitter a -> EndPolicy -- | The default splitting strategy: keep delimiters in the output as -- separate chunks, don't condense multiple consecutive delimiters into -- one, keep initial and final blank chunks. Default delimiter is the -- constantly false predicate. -- -- Note that defaultSplitter should normally not be used; use -- oneOf, onSublist, or whenElt instead, which are -- the same as the defaultSplitter with just the delimiter -- overridden. -- -- The defaultSplitter strategy with any delimiter gives a -- maximally information-preserving splitting strategy, in the sense that -- (a) taking the concat of the output yields the original list, -- and (b) given only the output list, we can reconstruct a -- Splitter which would produce the same output list again given -- the original input list. This default strategy can be overridden to -- allow discarding various sorts of information. defaultSplitter :: Splitter a -- | A delimiter can either be a predicate on elements, or a list of -- elements to be matched as a subsequence. data Delimiter a DelimEltPred :: (a -> Bool) -> Delimiter a DelimSublist :: [a] -> Delimiter a -- | Try to match a delimiter at the start of a list, either failing or -- decomposing the list into the portion which matched the delimiter and -- the remainder. matchDelim :: Delimiter a -> [a] -> Maybe ([a], [a]) -- | What to do with delimiters? data DelimPolicy -- | Drop delimiters from the output. Drop :: DelimPolicy -- | Keep delimiters as separate chunks of the output. Keep :: DelimPolicy -- | Keep delimiters in the output, prepending them to the following chunk. KeepLeft :: DelimPolicy -- | Keep delimiters in the output, appending them to the previous chunk. KeepRight :: DelimPolicy -- | What to do with multiple consecutive delimiters? data CondensePolicy -- | Condense into a single delimiter. Condense :: CondensePolicy -- | Insert blank chunks between consecutive delimiters. KeepBlankFields :: CondensePolicy -- | What to do with a blank chunk at either end of the list (i.e. when the -- list begins or ends with a delimiter). data EndPolicy DropBlank :: EndPolicy KeepBlank :: EndPolicy -- | Tag chunks as delimiters or text. data Chunk a Delim :: [a] -> Chunk a Text :: [a] -> Chunk a -- | Internal representation of a split list that tracks which pieces are -- delimiters and which aren't. type SplitList a = [Chunk a] -- | Untag a Chunk. fromElem :: Chunk a -> [a] -- | Test whether a Chunk is a delimiter. isDelim :: Chunk a -> Bool -- | Test whether a Chunk is text. isText :: Chunk a -> Bool -- | Standard build function. build :: (forall b. (a -> b -> b) -> b -> b) -> [a] -- | Given a delimiter to use, split a list into an internal representation -- with chunks tagged as delimiters or text. This transformation is -- lossless; in particular, concatMap fromElem -- (splitInternal d l) == l. splitInternal :: Delimiter a -> [a] -> SplitList a -- | Given a split list in the internal tagged representation, produce a -- new internal tagged representation corresponding to the final output, -- according to the strategy defined by the given Splitter. postProcess :: Splitter a -> SplitList a -> SplitList a -- | Drop delimiters if the DelimPolicy is Drop. doDrop :: DelimPolicy -> SplitList a -> SplitList a -- | Condense multiple consecutive delimiters into one if the -- CondensePolicy is Condense. doCondense :: CondensePolicy -> SplitList a -> SplitList a -- | Insert blank chunks between any remaining consecutive delimiters, and -- at the beginning or end if the first or last element is a delimiter. insertBlanks :: SplitList a -> SplitList a -- | Insert blank chunks between consecutive delimiters. insertBlanks' :: SplitList a -> SplitList a -- | Merge delimiters into adjacent chunks according to the -- DelimPolicy. doMerge :: DelimPolicy -> SplitList a -> SplitList a -- | Merge delimiters with adjacent chunks to the right (yes, that's not a -- typo: the delimiters should end up on the left of the chunks, so they -- are merged with chunks to their right). mergeLeft :: SplitList a -> SplitList a -- | Merge delimiters with adjacent chunks to the left. mergeRight :: SplitList a -> SplitList a -- | Drop an initial blank chunk according to the given EndPolicy. dropInitial :: EndPolicy -> SplitList a -> SplitList a -- | Drop a final blank chunk according to the given EndPolicy. dropFinal :: EndPolicy -> SplitList a -> SplitList a -- | Split a list according to the given splitting strategy. This is how to -- "run" a Splitter that has been built using the other -- combinators. split :: Splitter a -> [a] -> [[a]] -- | A splitting strategy that splits on any one of the given elements. For -- example: -- --
-- split (oneOf "xyz") "aazbxyzcxd" == ["aa","z","b","x","","y","","z","c","x","d"] --oneOf :: (Eq a) => [a] -> Splitter a -- | A splitting strategy that splits on the given list, when it is -- encountered as an exact subsequence. For example: -- --
-- split (onSublist "xyz") "aazbxyzcxd" == ["aazb","xyz","cxd"] ---- -- Note that splitting on the empty list is a special case, which splits -- just before every element of the list being split. For example: -- --
-- split (onSublist "") "abc" == ["","","a","","b","","c"] -- split (dropDelims . dropBlanks $ onSublist "") "abc" == ["a","b","c"] ---- -- However, if you want to break a list into singleton elements like -- this, you are better off using splitEvery 1, or better -- yet, map (:[]). onSublist :: (Eq a) => [a] -> Splitter a -- | A splitting strategy that splits on any elements that satisfy the -- given predicate. For example: -- --
-- split (whenElt (<0)) [2,4,-3,6,-9,1] == [[2,4],[-3],[6],[-9],[1]] --whenElt :: (a -> Bool) -> Splitter a -- | Drop delimiters from the output (the default is to keep them). For -- example, -- --
-- split (oneOf ":") "a:b:c" == ["a", ":", "b", ":", "c"] -- split (dropDelims $ oneOf ":") "a:b:c" == ["a", "b", "c"] --dropDelims :: Splitter a -> Splitter a -- | Keep delimiters in the output by prepending them to adjacent chunks. -- For example: -- --
-- split (keepDelimsL $ oneOf "xyz") "aazbxyzcxd" == ["aa","zb","x","y","zc","xd"] --keepDelimsL :: Splitter a -> Splitter a -- | Keep delimiters in the output by appending them to adjacent chunks. -- For example: -- --
-- split (keepDelimsR $ oneOf "xyz") "aazbxyzcxd" == ["aaz","bx","y","z","cx","d"] --keepDelimsR :: Splitter a -> Splitter a -- | Condense multiple consecutive delimiters into one. For example: -- --
-- split (condense $ oneOf "xyz") "aazbxyzcxd" == ["aa","z","b","xyz","c","x","d"] -- split (dropDelims $ oneOf "xyz") "aazbxyzcxd" == ["aa","b","","","c","d"] -- split (condense . dropDelims $ oneOf "xyz") "aazbxyzcxd" == ["aa","b","c","d"] --condense :: Splitter a -> Splitter a -- | Don't generate a blank chunk if there is a delimiter at the beginning. -- For example: -- --
-- split (oneOf ":") ":a:b" == ["",":","a",":","b"] -- split (dropInitBlank $ oneOf ":") ":a:b" == [":","a",":","b"] --dropInitBlank :: Splitter a -> Splitter a -- | Don't generate a blank chunk if there is a delimiter at the end. For -- example: -- --
-- split (oneOf ":") "a:b:" == ["a",":","b",":",""] -- split (dropFinalBlank $ oneOf ":") "a:b:" == ["a",":","b",":"] --dropFinalBlank :: Splitter a -> Splitter a -- | Drop all blank chunks from the output. Equivalent to -- dropInitBlank . dropFinalBlank . -- condense. For example: -- --
-- split (oneOf ":") "::b:::a" == ["",":","",":","b",":","",":","",":","a"] -- split (dropBlanks $ oneOf ":") "::b:::a" == ["::","b",":::","a"] --dropBlanks :: Splitter a -> Splitter a -- | Make a strategy that splits a list into chunks that all start with the -- given subsequence (except possibly the first). Equivalent to -- dropInitBlank . keepDelimsL . onSublist. -- For example: -- --
-- split (startsWith "app") "applyappicativeapplaudapproachapple" == ["apply","appicative","applaud","approach","apple"] --startsWith :: (Eq a) => [a] -> Splitter a -- | Make a strategy that splits a list into chunks that all start with one -- of the given elements (except possibly the first). Equivalent to -- dropInitBlank . keepDelimsL . oneOf. For -- example: -- --
-- split (startsWithOneOf ['A'..'Z']) "ACamelCaseIdentifier" == ["A","Camel","Case","Identifier"] --startsWithOneOf :: (Eq a) => [a] -> Splitter a -- | Make a strategy that splits a list into chunks that all end with the -- given subsequence, except possibly the last. Equivalent to -- dropFinalBlank . keepDelimsR . -- onSublist. For example: -- --
-- split (endsWith "ly") "happilyslowlygnarlylily" == ["happily","slowly","gnarly","lily"] --endsWith :: (Eq a) => [a] -> Splitter a -- | Make a strategy that splits a list into chunks that all end with one -- of the given elements, except possibly the last. Equivalent to -- dropFinalBlank . keepDelimsR . oneOf. -- For example: -- --
-- split (condense $ endsWithOneOf ".,?! ") "Hi, there! How are you?" == ["Hi, ","there! ","How ","are ","you?"] --endsWithOneOf :: (Eq a) => [a] -> Splitter a -- | Split on any of the given elements. Equivalent to split . -- dropDelims . oneOf. For example: -- --
-- splitOneOf ";.," "foo,bar;baz.glurk" == ["foo","bar","baz","glurk"] --splitOneOf :: (Eq a) => [a] -> [a] -> [[a]] -- | Split on the given sublist. Equivalent to split . -- dropDelims . onSublist. For example: -- --
-- splitOn ".." "a..b...c....d.." == ["a","b",".c","","d",""] --splitOn :: (Eq a) => [a] -> [a] -> [[a]] -- | Split on elements satisfying the given predicate. Equivalent to -- split . dropDelims . whenElt. For -- example: -- --
-- splitWhen (<0) [1,3,-4,5,7,-9,0,2] == [[1,3],[5,7],[0,2]] --splitWhen :: (a -> Bool) -> [a] -> [[a]] -- | A synonym for splitOn. sepBy :: (Eq a) => [a] -> [a] -> [[a]] -- | A synonym for splitOneOf. sepByOneOf :: (Eq a) => [a] -> [a] -> [[a]] -- | Split into chunks terminated by the given subsequence. Equivalent to -- split . dropFinalBlank . dropDelims . -- onSublist. For example: -- --
-- endBy ";" "foo;bar;baz;" == ["foo","bar","baz"] ---- -- Note also that the lines function from Data.List is -- equivalent to endBy "\n". endBy :: (Eq a) => [a] -> [a] -> [[a]] -- | Split into chunks terminated by one of the given elements. Equivalent -- to split . dropFinalBlank . dropDelims . -- oneOf. endByOneOf :: (Eq a) => [a] -> [a] -> [[a]] -- | A synonym for sepBy / splitOn. -- -- Note that this is the right inverse of the intercalate -- function from Data.List, that is, intercalate x . -- unintercalate x == id. It is also the case that -- unintercalate x . intercalate x is -- idempotent. unintercalate x . intercalate x -- is the identity on certain lists, but it is tricky to state the -- precise conditions under which this holds. (For example, it is not -- enough to say that x does not occur in any elements of the -- input list. Working out why is left as an exercise for the reader.) unintercalate :: (Eq a) => [a] -> [a] -> [[a]] -- | Split into words, with word boundaries indicated by the given -- predicate. Satisfies words === wordsBy isSpace; equivalent to -- split . dropBlanks . dropDelims . whenElt. For example: -- --
-- wordsBy (=='x') "dogxxxcatxbirdxx" == ["dog","cat","bird"] --wordsBy :: (a -> Bool) -> [a] -> [[a]] -- | Split into lines, with line boundaries indicated by the given -- predicate. Satisfies lines === linesBy (=='\n'); equivalent -- to split . dropFinalBlank . dropDelims . whenElt. For -- example: -- --
-- linesBy (=='x') "dogxxxcatxbirdxx" == ["dog","","","cat","bird",""] --linesBy :: (a -> Bool) -> [a] -> [[a]] -- | splitEvery n splits a list into length-n pieces. The -- last piece will be shorter if n does not evenly divide the -- length of the list. If n <= 0, splitEvery n -- l returns an infinite list of empty lists. splitEvery :: Int -> [e] -> [[e]] -- | A common synonym for splitEvery. chunk :: Int -> [e] -> [[e]] -- | Split a list into chunks of the given lengths. For example: -- --
-- splitPlaces [2,3,4] [1..20] == [[1,2],[3,4,5],[6,7,8,9]] -- splitPlaces [4,9] [1..10] == [[1,2,3,4],[5,6,7,8,9,10]] ---- -- The behavior of splitPlaces ls xs when sum -- ls /= length xs can be inferred from the above examples -- and the fact that splitPlaces is total. splitPlaces :: (Integral a) => [a] -> [e] -> [[e]] instance (Show a) => Show (Chunk a) instance (Eq a) => Eq (Chunk a) instance Eq EndPolicy instance Show EndPolicy instance Eq CondensePolicy instance Show CondensePolicy instance Eq DelimPolicy instance Show DelimPolicy -- | The Data.List.Split module contains a wide range of strategies -- for splitting lists with respect to some sort of delimiter, mostly -- implemented through a unified combinator interface. The goal is to be -- flexible yet simple. Scroll past the Synopsis for usage, examples, and -- detailed documentation of all exported functions. If you want to learn -- about the implementation, see Data.List.Split.Internals. -- -- A darcs repository containing the source (including a module with over -- 40 QuickCheck properties) can be found at -- http://code.haskell.org/~byorgey/code/split. module Data.List.Split -- | Split on the given sublist. Equivalent to split . -- dropDelims . onSublist. For example: -- --
-- splitOn ".." "a..b...c....d.." == ["a","b",".c","","d",""] --splitOn :: (Eq a) => [a] -> [a] -> [[a]] -- | Split on any of the given elements. Equivalent to split . -- dropDelims . oneOf. For example: -- --
-- splitOneOf ";.," "foo,bar;baz.glurk" == ["foo","bar","baz","glurk"] --splitOneOf :: (Eq a) => [a] -> [a] -> [[a]] -- | Split on elements satisfying the given predicate. Equivalent to -- split . dropDelims . whenElt. For -- example: -- --
-- splitWhen (<0) [1,3,-4,5,7,-9,0,2] == [[1,3],[5,7],[0,2]] --splitWhen :: (a -> Bool) -> [a] -> [[a]] -- | A synonym for splitOn. sepBy :: (Eq a) => [a] -> [a] -> [[a]] -- | A synonym for splitOneOf. sepByOneOf :: (Eq a) => [a] -> [a] -> [[a]] -- | Split into chunks terminated by the given subsequence. Equivalent to -- split . dropFinalBlank . dropDelims . -- onSublist. For example: -- --
-- endBy ";" "foo;bar;baz;" == ["foo","bar","baz"] ---- -- Note also that the lines function from Data.List is -- equivalent to endBy "\n". endBy :: (Eq a) => [a] -> [a] -> [[a]] -- | Split into chunks terminated by one of the given elements. Equivalent -- to split . dropFinalBlank . dropDelims . -- oneOf. endByOneOf :: (Eq a) => [a] -> [a] -> [[a]] -- | A synonym for sepBy / splitOn. -- -- Note that this is the right inverse of the intercalate -- function from Data.List, that is, intercalate x . -- unintercalate x == id. It is also the case that -- unintercalate x . intercalate x is -- idempotent. unintercalate x . intercalate x -- is the identity on certain lists, but it is tricky to state the -- precise conditions under which this holds. (For example, it is not -- enough to say that x does not occur in any elements of the -- input list. Working out why is left as an exercise for the reader.) unintercalate :: (Eq a) => [a] -> [a] -> [[a]] -- | Split into words, with word boundaries indicated by the given -- predicate. Satisfies words === wordsBy isSpace; equivalent to -- split . dropBlanks . dropDelims . whenElt. For example: -- --
-- wordsBy (=='x') "dogxxxcatxbirdxx" == ["dog","cat","bird"] --wordsBy :: (a -> Bool) -> [a] -> [[a]] -- | Split into lines, with line boundaries indicated by the given -- predicate. Satisfies lines === linesBy (=='\n'); equivalent -- to split . dropFinalBlank . dropDelims . whenElt. For -- example: -- --
-- linesBy (=='x') "dogxxxcatxbirdxx" == ["dog","","","cat","bird",""] --linesBy :: (a -> Bool) -> [a] -> [[a]] -- | splitEvery n splits a list into length-n pieces. The -- last piece will be shorter if n does not evenly divide the -- length of the list. If n <= 0, splitEvery n -- l returns an infinite list of empty lists. splitEvery :: Int -> [e] -> [[e]] -- | A common synonym for splitEvery. chunk :: Int -> [e] -> [[e]] -- | Split a list into chunks of the given lengths. For example: -- --
-- splitPlaces [2,3,4] [1..20] == [[1,2],[3,4,5],[6,7,8,9]] -- splitPlaces [4,9] [1..10] == [[1,2,3,4],[5,6,7,8,9,10]] ---- -- The behavior of splitPlaces ls xs when sum -- ls /= length xs can be inferred from the above examples -- and the fact that splitPlaces is total. splitPlaces :: (Integral a) => [a] -> [e] -> [[e]] -- | A splitting strategy. data Splitter a -- | The default splitting strategy: keep delimiters in the output as -- separate chunks, don't condense multiple consecutive delimiters into -- one, keep initial and final blank chunks. Default delimiter is the -- constantly false predicate. -- -- Note that defaultSplitter should normally not be used; use -- oneOf, onSublist, or whenElt instead, which are -- the same as the defaultSplitter with just the delimiter -- overridden. -- -- The defaultSplitter strategy with any delimiter gives a -- maximally information-preserving splitting strategy, in the sense that -- (a) taking the concat of the output yields the original list, -- and (b) given only the output list, we can reconstruct a -- Splitter which would produce the same output list again given -- the original input list. This default strategy can be overridden to -- allow discarding various sorts of information. defaultSplitter :: Splitter a -- | Split a list according to the given splitting strategy. This is how to -- "run" a Splitter that has been built using the other -- combinators. split :: Splitter a -> [a] -> [[a]] -- | A splitting strategy that splits on any one of the given elements. For -- example: -- --
-- split (oneOf "xyz") "aazbxyzcxd" == ["aa","z","b","x","","y","","z","c","x","d"] --oneOf :: (Eq a) => [a] -> Splitter a -- | A splitting strategy that splits on the given list, when it is -- encountered as an exact subsequence. For example: -- --
-- split (onSublist "xyz") "aazbxyzcxd" == ["aazb","xyz","cxd"] ---- -- Note that splitting on the empty list is a special case, which splits -- just before every element of the list being split. For example: -- --
-- split (onSublist "") "abc" == ["","","a","","b","","c"] -- split (dropDelims . dropBlanks $ onSublist "") "abc" == ["a","b","c"] ---- -- However, if you want to break a list into singleton elements like -- this, you are better off using splitEvery 1, or better -- yet, map (:[]). onSublist :: (Eq a) => [a] -> Splitter a -- | A splitting strategy that splits on any elements that satisfy the -- given predicate. For example: -- --
-- split (whenElt (<0)) [2,4,-3,6,-9,1] == [[2,4],[-3],[6],[-9],[1]] --whenElt :: (a -> Bool) -> Splitter a -- | Drop delimiters from the output (the default is to keep them). For -- example, -- --
-- split (oneOf ":") "a:b:c" == ["a", ":", "b", ":", "c"] -- split (dropDelims $ oneOf ":") "a:b:c" == ["a", "b", "c"] --dropDelims :: Splitter a -> Splitter a -- | Keep delimiters in the output by prepending them to adjacent chunks. -- For example: -- --
-- split (keepDelimsL $ oneOf "xyz") "aazbxyzcxd" == ["aa","zb","x","y","zc","xd"] --keepDelimsL :: Splitter a -> Splitter a -- | Keep delimiters in the output by appending them to adjacent chunks. -- For example: -- --
-- split (keepDelimsR $ oneOf "xyz") "aazbxyzcxd" == ["aaz","bx","y","z","cx","d"] --keepDelimsR :: Splitter a -> Splitter a -- | Condense multiple consecutive delimiters into one. For example: -- --
-- split (condense $ oneOf "xyz") "aazbxyzcxd" == ["aa","z","b","xyz","c","x","d"] -- split (dropDelims $ oneOf "xyz") "aazbxyzcxd" == ["aa","b","","","c","d"] -- split (condense . dropDelims $ oneOf "xyz") "aazbxyzcxd" == ["aa","b","c","d"] --condense :: Splitter a -> Splitter a -- | Don't generate a blank chunk if there is a delimiter at the beginning. -- For example: -- --
-- split (oneOf ":") ":a:b" == ["",":","a",":","b"] -- split (dropInitBlank $ oneOf ":") ":a:b" == [":","a",":","b"] --dropInitBlank :: Splitter a -> Splitter a -- | Don't generate a blank chunk if there is a delimiter at the end. For -- example: -- --
-- split (oneOf ":") "a:b:" == ["a",":","b",":",""] -- split (dropFinalBlank $ oneOf ":") "a:b:" == ["a",":","b",":"] --dropFinalBlank :: Splitter a -> Splitter a -- | Drop all blank chunks from the output. Equivalent to -- dropInitBlank . dropFinalBlank . -- condense. For example: -- --
-- split (oneOf ":") "::b:::a" == ["",":","",":","b",":","",":","",":","a"] -- split (dropBlanks $ oneOf ":") "::b:::a" == ["::","b",":::","a"] --dropBlanks :: Splitter a -> Splitter a -- | Make a strategy that splits a list into chunks that all start with the -- given subsequence (except possibly the first). Equivalent to -- dropInitBlank . keepDelimsL . onSublist. -- For example: -- --
-- split (startsWith "app") "applyappicativeapplaudapproachapple" == ["apply","appicative","applaud","approach","apple"] --startsWith :: (Eq a) => [a] -> Splitter a -- | Make a strategy that splits a list into chunks that all start with one -- of the given elements (except possibly the first). Equivalent to -- dropInitBlank . keepDelimsL . oneOf. For -- example: -- --
-- split (startsWithOneOf ['A'..'Z']) "ACamelCaseIdentifier" == ["A","Camel","Case","Identifier"] --startsWithOneOf :: (Eq a) => [a] -> Splitter a -- | Make a strategy that splits a list into chunks that all end with the -- given subsequence, except possibly the last. Equivalent to -- dropFinalBlank . keepDelimsR . -- onSublist. For example: -- --
-- split (endsWith "ly") "happilyslowlygnarlylily" == ["happily","slowly","gnarly","lily"] --endsWith :: (Eq a) => [a] -> Splitter a -- | Make a strategy that splits a list into chunks that all end with one -- of the given elements, except possibly the last. Equivalent to -- dropFinalBlank . keepDelimsR . oneOf. -- For example: -- --
-- split (condense $ endsWithOneOf ".,?! ") "Hi, there! How are you?" == ["Hi, ","there! ","How ","are ","you?"] --endsWithOneOf :: (Eq a) => [a] -> Splitter a