{-# OPTIONS_HADDOCK prune #-}

-- |
-- Module      :  Data.List.Split.Internals
-- Copyright   :  (c) Brent Yorgey, Louis Wasserman 2008-2012
-- License     :  BSD-style (see LICENSE)
-- Maintainer  :  Brent Yorgey <byorgey@gmail.com>
-- Stability   :  stable
-- Portability :  Haskell 2010
--
-- 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 where

import Data.List (genericSplitAt)

-- * Types and utilities

-- | A splitting strategy.
data Splitter a = Splitter
  { forall a. Splitter a -> Delimiter a
delimiter :: Delimiter a
  -- ^ What delimiter to split on
  , forall a. Splitter a -> DelimPolicy
delimPolicy :: DelimPolicy
  -- ^ What to do with delimiters (drop
  --   from output, keep as separate
  --   elements in output, or merge with
  --   previous or following chunks)
  , forall a. Splitter a -> CondensePolicy
condensePolicy :: CondensePolicy
  -- ^ What to do with multiple
  --   consecutive delimiters
  , forall a. Splitter a -> EndPolicy
initBlankPolicy :: EndPolicy
  -- ^ Drop an initial blank?
  , forall a. Splitter a -> EndPolicy
finalBlankPolicy :: EndPolicy
  -- ^ Drop a final blank?
  }

-- | 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
defaultSplitter :: forall a. Splitter a
defaultSplitter =
  Splitter
    { delimiter :: Delimiter a
delimiter = forall a. [a -> Bool] -> Delimiter a
Delimiter [forall a b. a -> b -> a
const Bool
False]
    , delimPolicy :: DelimPolicy
delimPolicy = DelimPolicy
Keep
    , condensePolicy :: CondensePolicy
condensePolicy = CondensePolicy
KeepBlankFields
    , initBlankPolicy :: EndPolicy
initBlankPolicy = EndPolicy
KeepBlank
    , finalBlankPolicy :: EndPolicy
finalBlankPolicy = EndPolicy
KeepBlank
    }

-- | A delimiter is a list of predicates on elements, matched by some
--   contiguous subsequence of a list.
newtype Delimiter a = Delimiter [a -> Bool]

-- | 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])
matchDelim :: forall a. Delimiter a -> [a] -> Maybe ([a], [a])
matchDelim (Delimiter []) [a]
xs = forall a. a -> Maybe a
Just ([], [a]
xs)
matchDelim (Delimiter [a -> Bool]
_) [] = forall a. Maybe a
Nothing
matchDelim (Delimiter (a -> Bool
p : [a -> Bool]
ps)) (a
x : [a]
xs)
  | a -> Bool
p a
x = forall a. Delimiter a -> [a] -> Maybe ([a], [a])
matchDelim (forall a. [a -> Bool] -> Delimiter a
Delimiter [a -> Bool]
ps) [a]
xs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \([a]
h, [a]
t) -> forall a. a -> Maybe a
Just (a
x forall a. a -> [a] -> [a]
: [a]
h, [a]
t)
  | Bool
otherwise = forall a. Maybe a
Nothing

-- | What to do with delimiters?
data DelimPolicy
  = -- | Drop delimiters from the output.
    Drop
  | -- | Keep delimiters as separate chunks
    --   of the output.
    Keep
  | -- | Keep delimiters in the output,
    --   prepending them to the following
    --   chunk.
    KeepLeft
  | -- | Keep delimiters in the output,
    --   appending them to the previous chunk.
    KeepRight
  deriving (DelimPolicy -> DelimPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DelimPolicy -> DelimPolicy -> Bool
$c/= :: DelimPolicy -> DelimPolicy -> Bool
== :: DelimPolicy -> DelimPolicy -> Bool
$c== :: DelimPolicy -> DelimPolicy -> Bool
Eq, Int -> DelimPolicy -> ShowS
[DelimPolicy] -> ShowS
DelimPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DelimPolicy] -> ShowS
$cshowList :: [DelimPolicy] -> ShowS
show :: DelimPolicy -> String
$cshow :: DelimPolicy -> String
showsPrec :: Int -> DelimPolicy -> ShowS
$cshowsPrec :: Int -> DelimPolicy -> ShowS
Show)

-- | What to do with multiple consecutive delimiters?
data CondensePolicy
  = -- | Condense into a single delimiter.
    Condense
  | -- | Keep consecutive
    --   delimiters separate, but
    --   don't insert blank chunks in
    --   between them.
    DropBlankFields
  | -- | Insert blank chunks
    --   between consecutive
    --   delimiters.
    KeepBlankFields
  deriving (CondensePolicy -> CondensePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CondensePolicy -> CondensePolicy -> Bool
$c/= :: CondensePolicy -> CondensePolicy -> Bool
== :: CondensePolicy -> CondensePolicy -> Bool
$c== :: CondensePolicy -> CondensePolicy -> Bool
Eq, Int -> CondensePolicy -> ShowS
[CondensePolicy] -> ShowS
CondensePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CondensePolicy] -> ShowS
$cshowList :: [CondensePolicy] -> ShowS
show :: CondensePolicy -> String
$cshow :: CondensePolicy -> String
showsPrec :: Int -> CondensePolicy -> ShowS
$cshowsPrec :: Int -> CondensePolicy -> ShowS
Show)

-- | 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 | KeepBlank
  deriving (EndPolicy -> EndPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EndPolicy -> EndPolicy -> Bool
$c/= :: EndPolicy -> EndPolicy -> Bool
== :: EndPolicy -> EndPolicy -> Bool
$c== :: EndPolicy -> EndPolicy -> Bool
Eq, Int -> EndPolicy -> ShowS
[EndPolicy] -> ShowS
EndPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EndPolicy] -> ShowS
$cshowList :: [EndPolicy] -> ShowS
show :: EndPolicy -> String
$cshow :: EndPolicy -> String
showsPrec :: Int -> EndPolicy -> ShowS
$cshowsPrec :: Int -> EndPolicy -> ShowS
Show)

-- | Tag chunks as delimiters or text.
data Chunk a = Delim [a] | Text [a]
  deriving (Int -> Chunk a -> ShowS
forall a. Show a => Int -> Chunk a -> ShowS
forall a. Show a => [Chunk a] -> ShowS
forall a. Show a => Chunk a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Chunk a] -> ShowS
$cshowList :: forall a. Show a => [Chunk a] -> ShowS
show :: Chunk a -> String
$cshow :: forall a. Show a => Chunk a -> String
showsPrec :: Int -> Chunk a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Chunk a -> ShowS
Show, Chunk a -> Chunk a -> Bool
forall a. Eq a => Chunk a -> Chunk a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Chunk a -> Chunk a -> Bool
$c/= :: forall a. Eq a => Chunk a -> Chunk a -> Bool
== :: Chunk a -> Chunk a -> Bool
$c== :: forall a. Eq a => Chunk a -> Chunk a -> Bool
Eq)

-- | 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]
fromElem :: forall a. Chunk a -> [a]
fromElem (Text [a]
as) = [a]
as
fromElem (Delim [a]
as) = [a]
as

-- | Test whether a 'Chunk' is a delimiter.
isDelim :: Chunk a -> Bool
isDelim :: forall a. Chunk a -> Bool
isDelim (Delim [a]
_) = Bool
True
isDelim Chunk a
_ = Bool
False

-- | Test whether a 'Chunk' is text.
isText :: Chunk a -> Bool
isText :: forall a. Chunk a -> Bool
isText (Text [a]
_) = Bool
True
isText Chunk a
_ = Bool
False

-- * Implementation

-- | 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
splitInternal :: forall a. Delimiter a -> [a] -> SplitList a
splitInternal Delimiter a
_ [] = []
splitInternal Delimiter a
d [a]
xxs
  | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
xs = Maybe ([a], [a]) -> [Chunk a]
toSplitList Maybe ([a], [a])
match
  | Bool
otherwise = forall a. [a] -> Chunk a
Text [a]
xs forall a. a -> [a] -> [a]
: Maybe ([a], [a]) -> [Chunk a]
toSplitList Maybe ([a], [a])
match
 where
  ([a]
xs, Maybe ([a], [a])
match) = forall a. Delimiter a -> [a] -> ([a], Maybe ([a], [a]))
breakDelim Delimiter a
d [a]
xxs

  toSplitList :: Maybe ([a], [a]) -> [Chunk a]
toSplitList Maybe ([a], [a])
Nothing = []
  toSplitList (Just ([], a
r : [a]
rs)) = forall a. [a] -> Chunk a
Delim [] forall a. a -> [a] -> [a]
: forall a. [a] -> Chunk a
Text [a
r] forall a. a -> [a] -> [a]
: forall a. Delimiter a -> [a] -> SplitList a
splitInternal Delimiter a
d [a]
rs
  toSplitList (Just ([a]
delim, [a]
rest)) = forall a. [a] -> Chunk a
Delim [a]
delim forall a. a -> [a] -> [a]
: forall a. Delimiter a -> [a] -> SplitList a
splitInternal Delimiter a
d [a]
rest

breakDelim :: Delimiter a -> [a] -> ([a], Maybe ([a], [a]))
breakDelim :: forall a. Delimiter a -> [a] -> ([a], Maybe ([a], [a]))
breakDelim (Delimiter []) [a]
xs = ([], forall a. a -> Maybe a
Just ([], [a]
xs))
breakDelim Delimiter a
_ [] = ([], forall a. Maybe a
Nothing)
breakDelim Delimiter a
d xxs :: [a]
xxs@(a
x : [a]
xs) =
  case forall a. Delimiter a -> [a] -> Maybe ([a], [a])
matchDelim Delimiter a
d [a]
xxs of
    Maybe ([a], [a])
Nothing -> let ([a]
ys, Maybe ([a], [a])
match) = forall a. Delimiter a -> [a] -> ([a], Maybe ([a], [a]))
breakDelim Delimiter a
d [a]
xs in (a
x forall a. a -> [a] -> [a]
: [a]
ys, Maybe ([a], [a])
match)
    Just ([a], [a])
match -> ([], forall a. a -> Maybe a
Just ([a], [a])
match)

-- | 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
postProcess :: forall a. Splitter a -> SplitList a -> SplitList a
postProcess Splitter a
s =
  forall a. EndPolicy -> SplitList a -> SplitList a
dropFinal (forall a. Splitter a -> EndPolicy
finalBlankPolicy Splitter a
s)
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. EndPolicy -> SplitList a -> SplitList a
dropInitial (forall a. Splitter a -> EndPolicy
initBlankPolicy Splitter a
s)
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. DelimPolicy -> SplitList a -> SplitList a
doMerge (forall a. Splitter a -> DelimPolicy
delimPolicy Splitter a
s)
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. DelimPolicy -> SplitList a -> SplitList a
doDrop (forall a. Splitter a -> DelimPolicy
delimPolicy Splitter a
s)
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. CondensePolicy -> SplitList a -> SplitList a
insertBlanks (forall a. Splitter a -> CondensePolicy
condensePolicy Splitter a
s)
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. CondensePolicy -> SplitList a -> SplitList a
doCondense (forall a. Splitter a -> CondensePolicy
condensePolicy Splitter a
s)

-- | Drop delimiters if the 'DelimPolicy' is 'Drop'.
doDrop :: DelimPolicy -> SplitList a -> SplitList a
doDrop :: forall a. DelimPolicy -> SplitList a -> SplitList a
doDrop DelimPolicy
Drop SplitList a
l = [Chunk a
c | c :: Chunk a
c@(Text [a]
_) <- SplitList a
l]
doDrop DelimPolicy
_ SplitList a
l = SplitList a
l

-- | Condense multiple consecutive delimiters into one if the
--   'CondensePolicy' is 'Condense'.
doCondense :: CondensePolicy -> SplitList a -> SplitList a
doCondense :: forall a. CondensePolicy -> SplitList a -> SplitList a
doCondense CondensePolicy
Condense SplitList a
ls = forall {a}. [Chunk a] -> [Chunk a]
condense' SplitList a
ls
 where
  condense' :: [Chunk a] -> [Chunk a]
condense' [] = []
  condense' (c :: Chunk a
c@(Text [a]
_) : [Chunk a]
l) = Chunk a
c forall a. a -> [a] -> [a]
: [Chunk a] -> [Chunk a]
condense' [Chunk a]
l
  condense' [Chunk a]
l = forall a. [a] -> Chunk a
Delim (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a. Chunk a -> [a]
fromElem [Chunk a]
ds) forall a. a -> [a] -> [a]
: [Chunk a] -> [Chunk a]
condense' [Chunk a]
rest
   where
    ([Chunk a]
ds, [Chunk a]
rest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
span forall a. Chunk a -> Bool
isDelim [Chunk a]
l
doCondense CondensePolicy
_ SplitList a
ls = SplitList a
ls

-- | Insert blank chunks between any remaining consecutive delimiters
--   (unless the condense policy is 'DropBlankFields'), and at the
--   beginning or end if the first or last element is a delimiter.
insertBlanks :: CondensePolicy -> SplitList a -> SplitList a
insertBlanks :: forall a. CondensePolicy -> SplitList a -> SplitList a
insertBlanks CondensePolicy
_ [] = [forall a. [a] -> Chunk a
Text []]
insertBlanks CondensePolicy
cp (d :: Chunk a
d@(Delim [a]
_) : [Chunk a]
l) = forall a. [a] -> Chunk a
Text [] forall a. a -> [a] -> [a]
: forall a. CondensePolicy -> SplitList a -> SplitList a
insertBlanks' CondensePolicy
cp (Chunk a
d forall a. a -> [a] -> [a]
: [Chunk a]
l)
insertBlanks CondensePolicy
cp [Chunk a]
l = forall a. CondensePolicy -> SplitList a -> SplitList a
insertBlanks' CondensePolicy
cp [Chunk a]
l

-- | Insert blank chunks between consecutive delimiters.
insertBlanks' :: CondensePolicy -> SplitList a -> SplitList a
insertBlanks' :: forall a. CondensePolicy -> SplitList a -> SplitList a
insertBlanks' CondensePolicy
_ [] = []
insertBlanks' cp :: CondensePolicy
cp@CondensePolicy
DropBlankFields (d1 :: Chunk a
d1@(Delim [a]
_) : d2 :: Chunk a
d2@(Delim [a]
_) : [Chunk a]
l) =
  Chunk a
d1 forall a. a -> [a] -> [a]
: forall a. CondensePolicy -> SplitList a -> SplitList a
insertBlanks' CondensePolicy
cp (Chunk a
d2 forall a. a -> [a] -> [a]
: [Chunk a]
l)
insertBlanks' CondensePolicy
cp (d1 :: Chunk a
d1@(Delim [a]
_) : d2 :: Chunk a
d2@(Delim [a]
_) : [Chunk a]
l) =
  Chunk a
d1 forall a. a -> [a] -> [a]
: forall a. [a] -> Chunk a
Text [] forall a. a -> [a] -> [a]
: forall a. CondensePolicy -> SplitList a -> SplitList a
insertBlanks' CondensePolicy
cp (Chunk a
d2 forall a. a -> [a] -> [a]
: [Chunk a]
l)
insertBlanks' CondensePolicy
_ [d :: Chunk a
d@(Delim [a]
_)] = [Chunk a
d, forall a. [a] -> Chunk a
Text []]
insertBlanks' CondensePolicy
cp (Chunk a
c : [Chunk a]
l) = Chunk a
c forall a. a -> [a] -> [a]
: forall a. CondensePolicy -> SplitList a -> SplitList a
insertBlanks' CondensePolicy
cp [Chunk a]
l

-- | Merge delimiters into adjacent chunks according to the 'DelimPolicy'.
doMerge :: DelimPolicy -> SplitList a -> SplitList a
doMerge :: forall a. DelimPolicy -> SplitList a -> SplitList a
doMerge DelimPolicy
KeepLeft = forall {a}. [Chunk a] -> [Chunk a]
mergeLeft
doMerge DelimPolicy
KeepRight = forall {a}. [Chunk a] -> [Chunk a]
mergeRight
doMerge DelimPolicy
_ = forall a. a -> a
id

-- | 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
mergeLeft :: forall {a}. [Chunk a] -> [Chunk a]
mergeLeft [] = []
mergeLeft ((Delim [a]
d) : (Text [a]
c) : [Chunk a]
l) = forall a. [a] -> Chunk a
Text ([a]
d forall a. [a] -> [a] -> [a]
++ [a]
c) forall a. a -> [a] -> [a]
: forall {a}. [Chunk a] -> [Chunk a]
mergeLeft [Chunk a]
l
mergeLeft (Chunk a
c : [Chunk a]
l) = Chunk a
c forall a. a -> [a] -> [a]
: forall {a}. [Chunk a] -> [Chunk a]
mergeLeft [Chunk a]
l

-- | Merge delimiters with adjacent chunks to the left.
mergeRight :: SplitList a -> SplitList a
mergeRight :: forall {a}. [Chunk a] -> [Chunk a]
mergeRight [] = []
-- below fanciness is with the goal of laziness: we want to start returning
-- stuff before we've necessarily discovered a delimiter, in case we're
-- processing some infinite list with no delimiter
mergeRight ((Text [a]
c) : [Chunk a]
l) = forall a. [a] -> Chunk a
Text ([a]
c forall a. [a] -> [a] -> [a]
++ [a]
d) forall a. a -> [a] -> [a]
: forall {a}. [Chunk a] -> [Chunk a]
mergeRight [Chunk a]
lTail
 where
  ([a]
d, [Chunk a]
lTail) = case [Chunk a]
l of
    Delim [a]
d' : [Chunk a]
l' -> ([a]
d', [Chunk a]
l')
    [Chunk a]
_ -> ([], [Chunk a]
l)
mergeRight (Chunk a
c : [Chunk a]
l) = Chunk a
c forall a. a -> [a] -> [a]
: forall {a}. [Chunk a] -> [Chunk a]
mergeRight [Chunk a]
l

-- | Drop an initial blank chunk according to the given 'EndPolicy'.
dropInitial :: EndPolicy -> SplitList a -> SplitList a
dropInitial :: forall a. EndPolicy -> SplitList a -> SplitList a
dropInitial EndPolicy
DropBlank (Text [] : [Chunk a]
l) = [Chunk a]
l
dropInitial EndPolicy
_ [Chunk a]
l = [Chunk a]
l

-- | Drop a final blank chunk according to the given 'EndPolicy'.
dropFinal :: EndPolicy -> SplitList a -> SplitList a
dropFinal :: forall a. EndPolicy -> SplitList a -> SplitList a
dropFinal EndPolicy
_ [] = []
dropFinal EndPolicy
DropBlank [Chunk a]
l = forall {a}. [Chunk a] -> [Chunk a]
dropFinal' [Chunk a]
l
 where
  dropFinal' :: [Chunk a] -> [Chunk a]
dropFinal' [] = []
  dropFinal' [Text []] = []
  dropFinal' (Chunk a
x : [Chunk a]
xs) = Chunk a
x forall a. a -> [a] -> [a]
: [Chunk a] -> [Chunk a]
dropFinal' [Chunk a]
xs
dropFinal EndPolicy
_ [Chunk a]
l = [Chunk a]
l

-- * Combinators

-- | 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]]
split :: forall a. Splitter a -> [a] -> [[a]]
split Splitter a
s = forall a b. (a -> b) -> [a] -> [b]
map forall a. Chunk a -> [a]
fromElem forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> SplitList a -> SplitList a
postProcess Splitter a
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Delimiter a -> [a] -> SplitList a
splitInternal (forall a. Splitter a -> Delimiter a
delimiter Splitter a
s)

-- ** Basic strategies

-- $ All these basic strategies have the same parameters as the
-- 'defaultSplitter' except for the delimiters.

-- | A splitting strategy that splits on any one of the given
--   elements.
--
-- >>> split (oneOf ",;") "hi;there,world"
-- ["hi",";","there",",","world"]
--
-- >>> split (oneOf "xyz") "aazbxyzcxd"
-- ["aa","z","b","x","","y","","z","c","x","d"]
oneOf :: (Eq a) => [a] -> Splitter a
oneOf :: forall a. Eq a => [a] -> Splitter a
oneOf [a]
elts = forall a. Splitter a
defaultSplitter {delimiter :: Delimiter a
delimiter = forall a. [a -> Bool] -> Delimiter a
Delimiter [(forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a]
elts)]}

-- | A splitting strategy that splits on the given list, when it is
--   encountered as an exact subsequence.
--
-- >>> 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.
--
-- >>> 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 @'chunksOf' 1@, or better yet,
--   @'map' (:[])@.
onSublist :: (Eq a) => [a] -> Splitter a
onSublist :: forall a. Eq a => [a] -> Splitter a
onSublist [a]
lst = forall a. Splitter a
defaultSplitter {delimiter :: Delimiter a
delimiter = forall a. [a -> Bool] -> Delimiter a
Delimiter (forall a b. (a -> b) -> [a] -> [b]
map forall a. Eq a => a -> a -> Bool
(==) [a]
lst)}

-- | A splitting strategy that splits on any elements that satisfy the
--   given predicate.
--
-- >>> split (whenElt (<0)) [2,4,-3,6,-9,1 :: Int]
-- [[2,4],[-3],[6],[-9],[1]]
whenElt :: (a -> Bool) -> Splitter a
whenElt :: forall a. (a -> Bool) -> Splitter a
whenElt a -> Bool
p = forall a. Splitter a
defaultSplitter {delimiter :: Delimiter a
delimiter = forall a. [a -> Bool] -> Delimiter a
Delimiter [a -> Bool
p]}

-- ** Strategy transformers

-- | Drop delimiters from the output (the default is to keep
--   them).
--
-- >>> split (oneOf ":") "a:b:c"
-- ["a",":","b",":","c"]
--
-- >>> split (dropDelims $ oneOf ":") "a:b:c"
-- ["a","b","c"]
dropDelims :: Splitter a -> Splitter a
dropDelims :: forall a. Splitter a -> Splitter a
dropDelims Splitter a
s = Splitter a
s {delimPolicy :: DelimPolicy
delimPolicy = DelimPolicy
Drop}

-- | Keep delimiters in the output by prepending them to adjacent
--   chunks.
--
-- >>> split (keepDelimsL $ oneOf "xyz") "aazbxyzcxd"
-- ["aa","zb","x","y","zc","xd"]
keepDelimsL :: Splitter a -> Splitter a
keepDelimsL :: forall a. Splitter a -> Splitter a
keepDelimsL Splitter a
s = Splitter a
s {delimPolicy :: DelimPolicy
delimPolicy = DelimPolicy
KeepLeft}

-- | Keep delimiters in the output by appending them to adjacent
--   chunks.
--
-- >>> split (keepDelimsR $ oneOf "xyz") "aazbxyzcxd"
-- ["aaz","bx","y","z","cx","d"]
keepDelimsR :: Splitter a -> Splitter a
keepDelimsR :: forall a. Splitter a -> Splitter a
keepDelimsR Splitter a
s = Splitter a
s {delimPolicy :: DelimPolicy
delimPolicy = DelimPolicy
KeepRight}

-- | Condense multiple consecutive delimiters into one.
--
-- >>> 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
condense :: forall a. Splitter a -> Splitter a
condense Splitter a
s = Splitter a
s {condensePolicy :: CondensePolicy
condensePolicy = CondensePolicy
Condense}

-- | Don't generate a blank chunk if there is a delimiter at the
--   beginning.
--
-- >>> split (oneOf ":") ":a:b"
-- ["",":","a",":","b"]
--
-- >>> split (dropInitBlank $ oneOf ":") ":a:b"
-- [":","a",":","b"]
dropInitBlank :: Splitter a -> Splitter a
dropInitBlank :: forall a. Splitter a -> Splitter a
dropInitBlank Splitter a
s = Splitter a
s {initBlankPolicy :: EndPolicy
initBlankPolicy = EndPolicy
DropBlank}

-- | Don't generate a blank chunk if there is a delimiter at the end.
--
-- >>> split (oneOf ":") "a:b:"
-- ["a",":","b",":",""]
--
-- >>> split (dropFinalBlank $ oneOf ":") "a:b:"
-- ["a",":","b",":"]
dropFinalBlank :: Splitter a -> Splitter a
dropFinalBlank :: forall a. Splitter a -> Splitter a
dropFinalBlank Splitter a
s = Splitter a
s {finalBlankPolicy :: EndPolicy
finalBlankPolicy = EndPolicy
DropBlank}

-- | Don't generate blank chunks between consecutive delimiters.
--
-- >>> split (oneOf ":") "::b:::a"
-- ["",":","",":","b",":","",":","",":","a"]
--
-- >>> split (dropInnerBlanks $ oneOf ":") "::b:::a"
-- ["",":",":","b",":",":",":","a"]
dropInnerBlanks :: Splitter a -> Splitter a
dropInnerBlanks :: forall a. Splitter a -> Splitter a
dropInnerBlanks Splitter a
s = Splitter a
s {condensePolicy :: CondensePolicy
condensePolicy = CondensePolicy
DropBlankFields}

-- ** Derived combinators

-- | Drop all blank chunks from the output, and condense consecutive
--   delimiters into one.  Equivalent to @'dropInitBlank'
--   . 'dropFinalBlank' . 'condense'@.
--
-- >>> split (oneOf ":") "::b:::a"
-- ["",":","",":","b",":","",":","",":","a"]
--
-- >>> split (dropBlanks $ oneOf ":") "::b:::a"
-- ["::","b",":::","a"]
dropBlanks :: Splitter a -> Splitter a
dropBlanks :: forall a. Splitter a -> Splitter a
dropBlanks = forall a. Splitter a -> Splitter a
dropInitBlank forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropFinalBlank forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
condense

-- | 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'@.
--
-- >>> split (startsWith "app") "applyapplicativeapplaudapproachapple"
-- ["apply","applicative","applaud","approach","apple"]
startsWith :: (Eq a) => [a] -> Splitter a
startsWith :: forall a. Eq a => [a] -> Splitter a
startsWith = forall a. Splitter a -> Splitter a
dropInitBlank forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
keepDelimsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> Splitter a
onSublist

-- | 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'@.
--   example:
--
-- >>> split (startsWithOneOf ['A'..'Z']) "ACamelCaseIdentifier"
-- ["A","Camel","Case","Identifier"]
startsWithOneOf :: (Eq a) => [a] -> Splitter a
startsWithOneOf :: forall a. Eq a => [a] -> Splitter a
startsWithOneOf = forall a. Splitter a -> Splitter a
dropInitBlank forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
keepDelimsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> Splitter a
oneOf

-- | 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'@.
--
-- >>> split (endsWith "ly") "happilyslowlygnarlylily"
-- ["happily","slowly","gnarly","lily"]
endsWith :: (Eq a) => [a] -> Splitter a
endsWith :: forall a. Eq a => [a] -> Splitter a
endsWith = forall a. Splitter a -> Splitter a
dropFinalBlank forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
keepDelimsR forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> Splitter a
onSublist

-- | 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'@.
--
-- >>> split (condense $ endsWithOneOf ".,?! ") "Hi, there!  How are you?"
-- ["Hi, ","there!  ","How ","are ","you?"]
endsWithOneOf :: (Eq a) => [a] -> Splitter a
endsWithOneOf :: forall a. Eq a => [a] -> Splitter a
endsWithOneOf = forall a. Splitter a -> Splitter a
dropFinalBlank forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
keepDelimsR forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> Splitter a
oneOf

-- ** Convenience functions

-- | Split on any of the given elements.  Equivalent to @'split'
--   . 'dropDelims' . 'oneOf'@.
--
-- >>> splitOneOf ";.," "foo,bar;baz.glurk"
-- ["foo","bar","baz","glurk"]
splitOneOf :: (Eq a) => [a] -> [a] -> [[a]]
splitOneOf :: forall a. Eq a => [a] -> [a] -> [[a]]
splitOneOf = forall a. Splitter a -> [a] -> [[a]]
split forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropDelims forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> Splitter a
oneOf

-- | Split on the given sublist.  Equivalent to @'split'
--   . 'dropDelims' . 'onSublist'@.
--
-- >>> splitOn ":" "12:35:07"
-- ["12","35","07"]
--
-- >>> splitOn "x" "axbxc"
-- ["a","b","c"]
--
-- >>> splitOn "x" "axbxcx"
-- ["a","b","c",""]
--
-- >>> splitOn ".." "a..b...c....d.."
-- ["a","b",".c","","d",""]
--
--   In some parsing combinator frameworks this is also known as
--   @sepBy@.
--
--   Note that this is the right inverse of the 'Data.List.intercalate' function
--   from "Data.List", that is,
--
-- @
-- intercalate x . splitOn x === id
-- @
--
--   @'splitOn' x . 'Data.List.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.)
splitOn :: (Eq a) => [a] -> [a] -> [[a]]
splitOn :: forall a. Eq a => [a] -> [a] -> [[a]]
splitOn = forall a. Splitter a -> [a] -> [[a]]
split forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropDelims forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> Splitter a
onSublist

-- | Split on elements satisfying the given predicate.  Equivalent to
--   @'split' . 'dropDelims' . 'whenElt'@.
--
-- >>> splitWhen (<0) [1,3,-4,5,7,-9,0,2]
-- [[1,3],[5,7],[0,2]]
--
-- >>> splitWhen (<0) [1,-2,3,4,-5,-6,7,8,-9]
-- [[1],[3,4],[],[7,8],[]]
splitWhen :: (a -> Bool) -> [a] -> [[a]]
splitWhen :: forall a. (a -> Bool) -> [a] -> [[a]]
splitWhen = forall a. Splitter a -> [a] -> [[a]]
split forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropDelims forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> Splitter a
whenElt

{-# DEPRECATED sepBy "Use splitOn." #-}
sepBy :: (Eq a) => [a] -> [a] -> [[a]]
sepBy :: forall a. Eq a => [a] -> [a] -> [[a]]
sepBy = forall a. Eq a => [a] -> [a] -> [[a]]
splitOn

{-# DEPRECATED sepByOneOf "Use splitOneOf." #-}
sepByOneOf :: (Eq a) => [a] -> [a] -> [[a]]
sepByOneOf :: forall a. Eq a => [a] -> [a] -> [[a]]
sepByOneOf = forall a. Eq a => [a] -> [a] -> [[a]]
splitOneOf

-- | Split into chunks terminated by the given subsequence.
--   Equivalent to @'split' . 'dropFinalBlank' . 'dropDelims'
--   . 'onSublist'@.
--
-- >>> 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]]
endBy :: forall a. Eq a => [a] -> [a] -> [[a]]
endBy = forall a. Splitter a -> [a] -> [[a]]
split forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropFinalBlank forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropDelims forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> Splitter a
onSublist

-- | Split into chunks terminated by one of the given elements.
--   Equivalent to @'split' . 'dropFinalBlank' . 'dropDelims'
--   . 'oneOf'@.
--
-- >>> endByOneOf ";," "foo;bar,baz;"
-- ["foo","bar","baz"]
endByOneOf :: (Eq a) => [a] -> [a] -> [[a]]
endByOneOf :: forall a. Eq a => [a] -> [a] -> [[a]]
endByOneOf = forall a. Splitter a -> [a] -> [[a]]
split forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropFinalBlank forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropDelims forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> Splitter a
oneOf

{-# DEPRECATED unintercalate "Use splitOn." #-}
unintercalate :: (Eq a) => [a] -> [a] -> [[a]]
unintercalate :: forall a. Eq a => [a] -> [a] -> [[a]]
unintercalate = forall a. Eq a => [a] -> [a] -> [[a]]
splitOn

-- | Split into \"words\", with word boundaries indicated by the given
--   predicate.  Satisfies @'Data.List.words' === wordsBy
--   'Data.Char.isSpace'@; equivalent to @'split' . 'dropBlanks'
--   . 'dropDelims' . 'whenElt'@.
--
-- >>> wordsBy (`elem` ",;.?! ") "Hello there, world! How?"
-- ["Hello","there","world","How"]
--
-- >>> wordsBy (=='x') "dogxxxcatxbirdxx"
-- ["dog","cat","bird"]
wordsBy :: (a -> Bool) -> [a] -> [[a]]
wordsBy :: forall a. (a -> Bool) -> [a] -> [[a]]
wordsBy = forall a. Splitter a -> [a] -> [[a]]
split forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropBlanks forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropDelims forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> Splitter a
whenElt

-- | Split into \"lines\", with line boundaries indicated by the given
--   predicate. Satisfies @'lines' === linesBy (=='\n')@; equivalent to
--   @'split' . 'dropFinalBlank' . 'dropDelims' . 'whenElt'@.
--
-- >>> linesBy (==';') "foo;bar;;baz;"
-- ["foo","bar","","baz"]
--
-- >>> linesBy (=='x') "dogxxxcatxbirdxx"
-- ["dog","","","cat","bird",""]
linesBy :: (a -> Bool) -> [a] -> [[a]]
linesBy :: forall a. (a -> Bool) -> [a] -> [[a]]
linesBy = forall a. Splitter a -> [a] -> [[a]]
split forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropFinalBlank forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Splitter a -> Splitter a
dropDelims forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> Splitter a
whenElt

-- * Other splitting methods

-- | Standard build function, specialized to building lists.
--
--   Usually build is given the rank-2 type
--
--   > build :: (forall b. (a -> b -> b) -> b -> b) -> [a]
--
--   but since we only use it when @(b ~ [a])@, we give it the more
--   restricted type signature in order to avoid needing a
--   non-Haskell2010 extension.
--
--   Note that the 0.1.4.3 release of this package did away with a
--   custom @build@ implementation in favor of importing one from
--   "GHC.Exts", which was (reportedly) faster for some applications.
--   However, in the interest of simplicity and complete Haskell2010
--   compliance as @split@ is being included in the Haskel Platform,
--   version 0.2.1.0 has gone back to defining @build@ manually.  This
--   is in line with @split@'s design philosophy of having efficiency
--   as a non-goal.
build :: ((a -> [a] -> [a]) -> [a] -> [a]) -> [a]
build :: forall a. ((a -> [a] -> [a]) -> [a] -> [a]) -> [a]
build (a -> [a] -> [a]) -> [a] -> [a]
g = (a -> [a] -> [a]) -> [a] -> [a]
g (:) []

-- | @'chunksOf' 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@, @'chunksOf' n l@ returns an infinite list
--   of empty lists.
--
-- >>> chunksOf 3 [1..12]
-- [[1,2,3],[4,5,6],[7,8,9],[10,11,12]]
--
-- >>> chunksOf 3 "Hello there"
-- ["Hel","lo ","the","re"]
--
-- >>> chunksOf 3 ([] :: [Int])
-- []
--
--   Note that @'chunksOf' n []@ is @[]@, not @[[]]@.  This is
--   intentional, and satisfies the property that
--
--   @chunksOf n xs ++ chunksOf n ys == chunksOf n (xs ++ ys)@
--
--   whenever @n@ evenly divides the length of @xs@.
chunksOf :: Int -> [e] -> [[e]]
chunksOf :: forall e. Int -> [e] -> [[e]]
chunksOf Int
i [e]
ls = forall a b. (a -> b) -> [a] -> [b]
map (forall a. Int -> [a] -> [a]
take Int
i) (forall a. ((a -> [a] -> [a]) -> [a] -> [a]) -> [a]
build (forall e a. [e] -> ([e] -> a -> a) -> a -> a
splitter [e]
ls))
 where
  splitter :: [e] -> ([e] -> a -> a) -> a -> a
  splitter :: forall e a. [e] -> ([e] -> a -> a) -> a -> a
splitter [] [e] -> a -> a
_ a
n = a
n
  splitter [e]
l [e] -> a -> a
c a
n = [e]
l [e] -> a -> a
`c` forall e a. [e] -> ([e] -> a -> a) -> a -> a
splitter (forall a. Int -> [a] -> [a]
drop Int
i [e]
l) [e] -> a -> a
c a
n

{-# DEPRECATED chunk "Use chunksOf." #-}
chunk :: Int -> [e] -> [[e]]
chunk :: forall e. Int -> [e] -> [[e]]
chunk = forall e. Int -> [e] -> [[e]]
chunksOf

{-# DEPRECATED splitEvery "Use chunksOf." #-}
splitEvery :: Int -> [e] -> [[e]]
splitEvery :: forall e. Int -> [e] -> [[e]]
splitEvery = forall e. Int -> [e] -> [[e]]
chunksOf

-- | Split a list into chunks of the given lengths.
--
-- >>> 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]]
--
-- >>> splitPlaces [4,9,3] [1..10]
-- [[1,2,3,4],[5,6,7,8,9,10]]
--
--   If the input list is longer than the total of the given lengths,
--   then the remaining elements are dropped. If the list is shorter
--   than the total of the given lengths, then the result may contain
--   fewer chunks than requested, and the last chunk may be shorter
--   than requested.
splitPlaces :: (Integral a) => [a] -> [e] -> [[e]]
splitPlaces :: forall a e. Integral a => [a] -> [e] -> [[e]]
splitPlaces [a]
is [e]
ys = forall a. ((a -> [a] -> [a]) -> [a] -> [a]) -> [a]
build (forall i b t. Integral i => [i] -> [b] -> ([b] -> t -> t) -> t -> t
splitPlacer [a]
is [e]
ys)
 where
  splitPlacer :: (Integral i) => [i] -> [b] -> ([b] -> t -> t) -> t -> t
  splitPlacer :: forall i b t. Integral i => [i] -> [b] -> ([b] -> t -> t) -> t -> t
splitPlacer [] [b]
_ [b] -> t -> t
_ t
n = t
n
  splitPlacer [i]
_ [] [b] -> t -> t
_ t
n = t
n
  splitPlacer (i
l : [i]
ls) [b]
xs [b] -> t -> t
c t
n =
    let ([b]
x1, [b]
x2) = forall i a. Integral i => i -> [a] -> ([a], [a])
genericSplitAt i
l [b]
xs
     in [b]
x1 [b] -> t -> t
`c` forall i b t. Integral i => [i] -> [b] -> ([b] -> t -> t) -> t -> t
splitPlacer [i]
ls [b]
x2 [b] -> t -> t
c t
n

-- | Split a list into chunks of the given lengths. Unlike
--   'splitPlaces', the output list will always be the same length as
--   the first input argument. If the input list is longer than the
--   total of the given lengths, then the remaining elements are
--   dropped. If the list is shorter than the total of the given
--   lengths, then the last several chunks will be shorter than
--   requested or empty.
--
-- >>> splitPlacesBlanks [2,3,4] [1..20]
-- [[1,2],[3,4,5],[6,7,8,9]]
--
-- >>> splitPlacesBlanks [4,9] [1..10]
-- [[1,2,3,4],[5,6,7,8,9,10]]
--
-- >>> splitPlacesBlanks [4,9,3] [1..10]
-- [[1,2,3,4],[5,6,7,8,9,10],[]]
--
--   Notice the empty list in the output of the third example, which
--   differs from the behavior of 'splitPlaces'.
splitPlacesBlanks :: (Integral a) => [a] -> [e] -> [[e]]
splitPlacesBlanks :: forall a e. Integral a => [a] -> [e] -> [[e]]
splitPlacesBlanks [a]
is [e]
ys = forall a. ((a -> [a] -> [a]) -> [a] -> [a]) -> [a]
build (forall i b t. Integral i => [i] -> [b] -> ([b] -> t -> t) -> t -> t
splitPlacer [a]
is [e]
ys)
 where
  splitPlacer :: (Integral i) => [i] -> [b] -> ([b] -> t -> t) -> t -> t
  splitPlacer :: forall i b t. Integral i => [i] -> [b] -> ([b] -> t -> t) -> t -> t
splitPlacer [] [b]
_ [b] -> t -> t
_ t
n = t
n
  splitPlacer (i
l : [i]
ls) [b]
xs [b] -> t -> t
c t
n =
    let ([b]
x1, [b]
x2) = forall i a. Integral i => i -> [a] -> ([a], [a])
genericSplitAt i
l [b]
xs
     in [b]
x1 [b] -> t -> t
`c` forall i b t. Integral i => [i] -> [b] -> ([b] -> t -> t) -> t -> t
splitPlacer [i]
ls [b]
x2 [b] -> t -> t
c t
n

-- | A useful recursion pattern for processing a list to produce a new
--   list, often used for \"chopping\" up the input list.  Typically
--   chop is called with some function that will consume an initial
--   prefix of the list and produce a value and the rest of the list.
--
--   For example, many common Prelude functions can be implemented in
--   terms of @chop@:
--
-- > group :: (Eq a) => [a] -> [[a]]
-- > group = chop (\ xs@(x:_) -> span (==x) xs)
-- >
-- > words :: String -> [String]
-- > words = filter (not . null) . chop (break isSpace . dropWhile isSpace)
chop :: ([a] -> (b, [a])) -> [a] -> [b]
chop :: forall a b. ([a] -> (b, [a])) -> [a] -> [b]
chop [a] -> (b, [a])
_ [] = []
chop [a] -> (b, [a])
f [a]
as = b
b forall a. a -> [a] -> [a]
: forall a b. ([a] -> (b, [a])) -> [a] -> [b]
chop [a] -> (b, [a])
f [a]
as'
 where
  (b
b, [a]
as') = [a] -> (b, [a])
f [a]
as

-- | Divides up an input list into a set of sublists, according to 'n' and 'm'
--   input specifications you provide. Each sublist will have 'n' items, and the
--   start of each sublist will be offset by 'm' items from the previous one.
--
-- >>> divvy 5 5 [1..15]
-- [[1,2,3,4,5],[6,7,8,9,10],[11,12,13,14,15]]
--
-- >>> divvy 5 2 [1..15]
-- [[1,2,3,4,5],[3,4,5,6,7],[5,6,7,8,9],[7,8,9,10,11],[9,10,11,12,13],[11,12,13,14,15]]
--
--   In the case where a source list's trailing elements do no fill an entire
--   sublist, those trailing elements will be dropped.
--
-- >>> divvy 5 2 [1..10]
-- [[1,2,3,4,5],[3,4,5,6,7],[5,6,7,8,9]]
--
--   As an example, you can generate a moving average over a list of prices:
--
-- > type Prices = [Float]
-- > type AveragePrices = [Float]
-- >
-- > average :: [Float] -> Float
-- > average xs = sum xs / (fromIntegral $ length xs)
-- >
-- > simpleMovingAverage :: Prices -> AveragePrices
-- > simpleMovingAverage = map average . divvy 20 1
divvy :: Int -> Int -> [a] -> [[a]]
divvy :: forall a. Int -> Int -> [a] -> [[a]]
divvy Int
_ Int
_ [] = []
divvy Int
n Int
m [a]
lst = forall a. (a -> Bool) -> [a] -> [a]
filter ((Int
n forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Int
length) [[a]]
choppedl
 where
  choppedl :: [[a]]
choppedl = forall a b. ([a] -> (b, [a])) -> [a] -> [b]
chop (\[a]
xs -> (forall a. Int -> [a] -> [a]
take Int
n [a]
xs, forall a. Int -> [a] -> [a]
drop Int
m [a]
xs)) [a]
lst