{-# LANGUAGE Safe #-}

{- arch-tag: List utilities main file
Copyright (c) 2004-2011 John Goerzen <jgoerzen@complete.org>

All rights reserved.

For license and copyright information, see the file LICENSE
-}

{- |
   Module     : Data.List.Utils
   Copyright  : Copyright (C) 2004-2011 John Goerzen
   SPDX-License-Identifier: BSD-3-Clause

   Stability  : stable
   Portability: portable

This module provides various helpful utilities for dealing with lists.

Written by John Goerzen, jgoerzen\@complete.org
-}

module Data.List.Utils(-- * Merging
                     merge, mergeBy,
                     -- * Tests
                     startswith, endswith, contains, hasAny,
                     -- * Association List Utilities
                     {- | These functions are designed to augment the
                     association list functions in "Data.List" and
                     provide an interface similar to "Data.FiniteMap" or
                     "Data.Map"
                     for association lists. -}
                     addToAL, delFromAL, flipAL, keysAL, valuesAL,
                     hasKeyAL,
                     -- ** Association List Conversions
                     strFromAL,
                     strToAL,
                     -- * Conversions
                     split, join, replace, genericJoin, takeWhileList,
                     dropWhileList, spanList, breakList,
                     -- ** Advanced Conversions
                     WholeFunc(..), wholeMap, fixedWidth,
                     -- * Fixed-Width and State Monad Utilities
                     grab,
                     -- * Miscellaneous
                     countElem, elemRIndex, alwaysElemRIndex, seqList,
                     subIndex, uniq
                     -- -- * Sub-List Selection
                     -- sub,
                    ) where

import           Control.Monad.State (State, get, put)
import           Data.List           (elemIndices, findIndex, intercalate,
                                      isInfixOf, isPrefixOf, isSuffixOf, nub,
                                      tails)


{- | Merge two sorted lists into a single, sorted whole.

Example:

> merge [1,3,5] [1,2,4,6] -> [1,1,2,3,4,5,6]

QuickCheck test property:

prop_merge xs ys =
    merge (sort xs) (sort ys) == sort (xs ++ ys)
          where types = xs :: [Int]
-}
merge ::  (Ord a) => [a] -> [a] -> [a]
merge :: [a] -> [a] -> [a]
merge = (a -> a -> Ordering) -> [a] -> [a] -> [a]
forall a. (a -> a -> Ordering) -> [a] -> [a] -> [a]
mergeBy (a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare)

{- | Merge two sorted lists using into a single, sorted whole,
allowing the programmer to specify the comparison function.

QuickCheck test property:

prop_mergeBy xs ys =
    mergeBy cmp (sortBy cmp xs) (sortBy cmp ys) == sortBy cmp (xs ++ ys)
          where types = xs :: [ (Int, Int) ]
                cmp (x1,_) (x2,_) = compare x1 x2
-}
mergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
mergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
mergeBy a -> a -> Ordering
_   [] [a]
ys = [a]
ys
mergeBy a -> a -> Ordering
_   [a]
xs [] = [a]
xs
mergeBy a -> a -> Ordering
cmp (allx :: [a]
allx@(a
x:[a]
xs)) (ally :: [a]
ally@(a
y:[a]
ys))
        -- Ordering derives Eq, Ord, so the comparison below is valid.
        -- Explanation left as an exercise for the reader.
        -- Someone please put this code out of its misery.
    | (a
x a -> a -> Ordering
`cmp` a
y) Ordering -> Ordering -> Bool
forall a. Ord a => a -> a -> Bool
<= Ordering
EQ = a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: (a -> a -> Ordering) -> [a] -> [a] -> [a]
forall a. (a -> a -> Ordering) -> [a] -> [a] -> [a]
mergeBy a -> a -> Ordering
cmp [a]
xs [a]
ally
    | Bool
otherwise = a
y a -> [a] -> [a]
forall a. a -> [a] -> [a]
: (a -> a -> Ordering) -> [a] -> [a] -> [a]
forall a. (a -> a -> Ordering) -> [a] -> [a] -> [a]
mergeBy a -> a -> Ordering
cmp [a]
allx [a]
ys

{- | Returns true if the given list starts with the specified elements;
false otherwise.  (This is an alias for 'Data.List.isPrefixOf'.)

Example:

> startswith "He" "Hello" -> True

-}

startswith :: Eq a => [a] -> [a] -> Bool
startswith :: [a] -> [a] -> Bool
startswith = [a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf

{- | Returns true if the given list ends with the specified elements;
false otherwise.  (This is an alias for 'Data.List.isSuffixOf'.)

Example:

> endswith "lo" "Hello" -> True

-}
endswith :: Eq a => [a] -> [a] -> Bool
endswith :: [a] -> [a] -> Bool
endswith = [a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf

{- | Returns true if the given list contains any of the elements in the search
list. -}
hasAny :: Eq a => [a]           -- ^ List of elements to look for
       -> [a]                   -- ^ List to search
       -> Bool                  -- ^ Result
hasAny :: [a] -> [a] -> Bool
hasAny [] [a]
_          = Bool
False             -- An empty search list: always false
hasAny [a]
_ []          = Bool
False             -- An empty list to scan: always false
hasAny [a]
search (a
x:[a]
xs) = if a
x a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a]
search then Bool
True else [a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
hasAny [a]
search [a]
xs

{- | Similar to 'Data.List.takeWhile', takes elements while the func is true.
The function is given the remainder of the list to examine. -}
takeWhileList :: ([a] -> Bool) -> [a] -> [a]
takeWhileList :: ([a] -> Bool) -> [a] -> [a]
takeWhileList [a] -> Bool
_ [] = []
takeWhileList [a] -> Bool
func list :: [a]
list@(a
x:[a]
xs) =
    if [a] -> Bool
func [a]
list
       then a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: ([a] -> Bool) -> [a] -> [a]
forall a. ([a] -> Bool) -> [a] -> [a]
takeWhileList [a] -> Bool
func [a]
xs
       else []

{- | Similar to 'Data.List.dropWhile', drops elements while the func is true.
The function is given the remainder of the list to examine. -}
dropWhileList :: ([a] -> Bool) -> [a] -> [a]
dropWhileList :: ([a] -> Bool) -> [a] -> [a]
dropWhileList [a] -> Bool
_ [] = []
dropWhileList [a] -> Bool
func list :: [a]
list@(a
_:[a]
xs) =
    if [a] -> Bool
func [a]
list
       then ([a] -> Bool) -> [a] -> [a]
forall a. ([a] -> Bool) -> [a] -> [a]
dropWhileList [a] -> Bool
func [a]
xs
       else [a]
list

{- | Similar to 'Data.List.span', but performs the test on the entire remaining
list instead of just one element.

@spanList p xs@ is the same as @(takeWhileList p xs, dropWhileList p xs)@
-}
spanList :: ([a] -> Bool) -> [a] -> ([a], [a])

spanList :: ([a] -> Bool) -> [a] -> ([a], [a])
spanList [a] -> Bool
_ [] = ([],[])
spanList [a] -> Bool
func list :: [a]
list@(a
x:[a]
xs) =
    if [a] -> Bool
func [a]
list
       then (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
ys,[a]
zs)
       else ([],[a]
list)
    where ([a]
ys,[a]
zs) = ([a] -> Bool) -> [a] -> ([a], [a])
forall a. ([a] -> Bool) -> [a] -> ([a], [a])
spanList [a] -> Bool
func [a]
xs

{- | Similar to 'Data.List.break', but performs the test on the entire remaining
list instead of just one element.
-}
breakList :: ([a] -> Bool) -> [a] -> ([a], [a])
breakList :: ([a] -> Bool) -> [a] -> ([a], [a])
breakList [a] -> Bool
func = ([a] -> Bool) -> [a] -> ([a], [a])
forall a. ([a] -> Bool) -> [a] -> ([a], [a])
spanList (Bool -> Bool
not (Bool -> Bool) -> ([a] -> Bool) -> [a] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Bool
func)

{- | Given a delimiter and a list (or string), split into components.

Example:

> split "," "foo,bar,,baz," -> ["foo", "bar", "", "baz", ""]

> split "ba" ",foo,bar,,baz," -> [",foo,","r,,","z,"]
-}
split :: Eq a => [a] -> [a] -> [[a]]
split :: [a] -> [a] -> [[a]]
split [a]
_ [] = []
split [a]
delim [a]
str =
    let ([a]
firstline, [a]
remainder) = ([a] -> Bool) -> [a] -> ([a], [a])
forall a. ([a] -> Bool) -> [a] -> ([a], [a])
breakList ([a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
startswith [a]
delim) [a]
str
        in
        [a]
firstline [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: case [a]
remainder of
                                   [] -> []
                                   [a]
x -> if [a]
x [a] -> [a] -> Bool
forall a. Eq a => a -> a -> Bool
== [a]
delim
                                        then [] [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: []
                                        else [a] -> [a] -> [[a]]
forall a. Eq a => [a] -> [a] -> [[a]]
split [a]
delim
                                                 (Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop ([a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
delim) [a]
x)


{- | Given a list and a replacement list, replaces each occurance of the search
list with the replacement list in the operation list.

Example:

>replace "," "." "127,0,0,1" -> "127.0.0.1"

This could logically be thought of as:

>replace old new l = join new . split old $ l
-}

replace :: Eq a => [a] -> [a] -> [a] -> [a]
replace :: [a] -> [a] -> [a] -> [a]
replace [a]
old [a]
new [a]
l = [a] -> [[a]] -> [a]
forall a. [a] -> [[a]] -> [a]
join [a]
new ([[a]] -> [a]) -> ([a] -> [[a]]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [a] -> [[a]]
forall a. Eq a => [a] -> [a] -> [[a]]
split [a]
old ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ [a]
l

{- | Given a delimiter and a list of items (or strings), join the items
by using the delimiter.  Alias for 'Data.List.intercalate'.

Example:

> join "|" ["foo", "bar", "baz"] -> "foo|bar|baz"
-}
join :: [a] -> [[a]] -> [a]
join :: [a] -> [[a]] -> [a]
join = [a] -> [[a]] -> [a]
forall a. [a] -> [[a]] -> [a]
intercalate

{- | Like 'join', but works with a list of anything showable, converting
it to a String.

Examples:

> genericJoin ", " [1, 2, 3, 4] -> "1, 2, 3, 4"
> genericJoin "|" ["foo", "bar", "baz"] -> "\"foo\"|\"bar\"|\"baz\""

-}
genericJoin :: Show a => String -> [a] -> String
genericJoin :: String -> [a] -> String
genericJoin String
delim [a]
l = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
join String
delim ((a -> String) -> [a] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map a -> String
forall a. Show a => a -> String
show [a]
l)

{- | Returns true if the given parameter is a sublist of the given list;
false otherwise.  Alias for 'Data.List.isInfixOf'.

Example:

> contains "Haskell" "I really like Haskell." -> True
> contains "Haskell" "OCaml is great." -> False

-}

contains :: Eq a => [a] -> [a] -> Bool
contains :: [a] -> [a] -> Bool
contains = [a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isInfixOf

-- above function submitted to GHC as Data.List.isInfixOf on 8/31/2006

{- | Adds the specified (key, value) pair to the given list, removing any
existing pair with the same key already present. -}
addToAL :: Eq key => [(key, elt)] -> key -> elt -> [(key, elt)]
addToAL :: [(key, elt)] -> key -> elt -> [(key, elt)]
addToAL [(key, elt)]
l key
key elt
value = (key
key, elt
value) (key, elt) -> [(key, elt)] -> [(key, elt)]
forall a. a -> [a] -> [a]
: [(key, elt)] -> key -> [(key, elt)]
forall key a. Eq key => [(key, a)] -> key -> [(key, a)]
delFromAL [(key, elt)]
l key
key

{- | Removes all (key, value) pairs from the given list where the key
matches the given one. -}
delFromAL :: Eq key => [(key, a)] -> key -> [(key, a)]
delFromAL :: [(key, a)] -> key -> [(key, a)]
delFromAL [(key, a)]
l key
key = ((key, a) -> Bool) -> [(key, a)] -> [(key, a)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(key, a)
a -> ((key, a) -> key
forall a b. (a, b) -> a
fst (key, a)
a) key -> key -> Bool
forall a. Eq a => a -> a -> Bool
/= key
key) [(key, a)]
l

{- | Returns the keys that comprise the (key, value) pairs of the given AL.

Same as:

>map fst
-}
keysAL :: [(key, a)] -> [key]
keysAL :: [(key, a)] -> [key]
keysAL = ((key, a) -> key) -> [(key, a)] -> [key]
forall a b. (a -> b) -> [a] -> [b]
map (key, a) -> key
forall a b. (a, b) -> a
fst

{- | Returns the values the comprise the (key, value) pairs of the given
AL.

Same as:

>map snd
-}
valuesAL :: [(a, value)] -> [value]
valuesAL :: [(a, value)] -> [value]
valuesAL = ((a, value) -> value) -> [(a, value)] -> [value]
forall a b. (a -> b) -> [a] -> [b]
map (a, value) -> value
forall a b. (a, b) -> b
snd

{- | Indicates whether or not the given key is in the AL. -}
hasKeyAL :: Eq a => a -> [(a, b)] -> Bool
hasKeyAL :: a -> [(a, b)] -> Bool
hasKeyAL a
key [(a, b)]
list =
    a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
key ([(a, b)] -> [a]
forall key a. [(key, a)] -> [key]
keysAL [(a, b)]
list)

{- | Flips an association list.  Converts (key1, val), (key2, val) pairs
to (val, [key1, key2]). -}
flipAL :: (Eq key, Eq val) => [(key, val)] -> [(val, [key])]
flipAL :: [(key, val)] -> [(val, [key])]
flipAL [(key, val)]
oldl =
    let worker :: (Eq key, Eq val) => [(key, val)] -> [(val, [key])] -> [(val, [key])]
        worker :: [(key, val)] -> [(val, [key])] -> [(val, [key])]
worker [] [(val, [key])]
accum = [(val, [key])]
accum
        worker ((key
k, val
v):[(key, val)]
xs) [(val, [key])]
accum =
            case val -> [(val, [key])] -> Maybe [key]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup val
v [(val, [key])]
accum of
                                Maybe [key]
Nothing -> [(key, val)] -> [(val, [key])] -> [(val, [key])]
forall key val.
(Eq key, Eq val) =>
[(key, val)] -> [(val, [key])] -> [(val, [key])]
worker [(key, val)]
xs ((val
v, [key
k]) (val, [key]) -> [(val, [key])] -> [(val, [key])]
forall a. a -> [a] -> [a]
: [(val, [key])]
accum)
                                Just [key]
y  -> [(key, val)] -> [(val, [key])] -> [(val, [key])]
forall key val.
(Eq key, Eq val) =>
[(key, val)] -> [(val, [key])] -> [(val, [key])]
worker [(key, val)]
xs ([(val, [key])] -> val -> [key] -> [(val, [key])]
forall key elt.
Eq key =>
[(key, elt)] -> key -> elt -> [(key, elt)]
addToAL [(val, [key])]
accum val
v (key
kkey -> [key] -> [key]
forall a. a -> [a] -> [a]
:[key]
y))
        in
        [(key, val)] -> [(val, [key])] -> [(val, [key])]
forall key val.
(Eq key, Eq val) =>
[(key, val)] -> [(val, [key])] -> [(val, [key])]
worker [(key, val)]
oldl []

{- | Converts an association list to a string.  The string will have
one pair per line, with the key and value both represented as a Haskell string.

This function is designed to work with [(String, String)] association lists,
but may work with other types as well. -}

strFromAL :: (Show a, Show b) => [(a, b)] -> String
strFromAL :: [(a, b)] -> String
strFromAL [(a, b)]
inp =
    let worker :: (a, a) -> String
worker (a
key, a
val) = a -> String
forall a. Show a => a -> String
show a
key String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"," String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
val
        in [String] -> String
unlines ([String] -> String)
-> ([(a, b)] -> [String]) -> [(a, b)] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b) -> String) -> [(a, b)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (a, b) -> String
forall a a. (Show a, Show a) => (a, a) -> String
worker ([(a, b)] -> String) -> [(a, b)] -> String
forall a b. (a -> b) -> a -> b
$ [(a, b)]
inp

{- | The inverse of 'strFromAL', this function reads a string and outputs the
appropriate association list.

Like 'strFromAL', this is designed to work with [(String, String)] association
lists but may also work with other objects with simple representations.
-}
strToAL :: (Read a, Read b) => String -> [(a, b)]
strToAL :: String -> [(a, b)]
strToAL String
inp =
    let worker :: String -> (a, b)
worker String
line =
            case ReadS a
forall a. Read a => ReadS a
reads String
line of
               [(a
key, String
remainder)] -> case String
remainder of
                     Char
',':String
valstr -> (a
key, String -> b
forall a. Read a => String -> a
read String
valstr)
                     String
_ -> String -> (a, b)
forall a. HasCallStack => String -> a
error String
"Data.List.Utils.strToAL: Parse error on value"
               [(a, String)]
_ -> String -> (a, b)
forall a. HasCallStack => String -> a
error String
"Data.List.Utils.strToAL: Parse error on key"
        in (String -> (a, b)) -> [String] -> [(a, b)]
forall a b. (a -> b) -> [a] -> [b]
map String -> (a, b)
forall a b. (Read a, Read b) => String -> (a, b)
worker (String -> [String]
lines String
inp)


{- FIXME TODO: sub -}

{- | Returns a count of the number of times the given element occured in the
given list. -}
countElem :: Eq a => a -> [a] -> Int
countElem :: a -> [a] -> Int
countElem a
i = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([a] -> Int) -> ([a] -> [a]) -> [a] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
filter (a
ia -> a -> Bool
forall a. Eq a => a -> a -> Bool
==)

{- | Returns the rightmost index of the given element in the
given list. -}
elemRIndex :: Eq a => a -> [a] -> Maybe Int
elemRIndex :: a -> [a] -> Maybe Int
elemRIndex a
item [a]
l =
    case [Int] -> [Int]
forall a. [a] -> [a]
reverse ([Int] -> [Int]) -> [Int] -> [Int]
forall a b. (a -> b) -> a -> b
$ a -> [a] -> [Int]
forall a. Eq a => a -> [a] -> [Int]
elemIndices a
item [a]
l of
                                   []    -> Maybe Int
forall a. Maybe a
Nothing
                                   (Int
x:[Int]
_) -> Int -> Maybe Int
forall a. a -> Maybe a
Just Int
x
{- | Like elemRIndex, but returns -1 if there is nothing
found. -}
alwaysElemRIndex :: Eq a => a -> [a] -> Int
alwaysElemRIndex :: a -> [a] -> Int
alwaysElemRIndex a
item [a]
list =
    case a -> [a] -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
elemRIndex a
item [a]
list of
                              Maybe Int
Nothing -> -Int
1
                              Just Int
x  -> Int
x

{- | Forces the evaluation of the entire list. -}
seqList :: [a] -> [a]
seqList :: [a] -> [a]
seqList []          = []
seqList list :: [a]
list@(a
_:[a]
xs) = [a] -> [a] -> [a]
seq ([a] -> [a]
forall a. [a] -> [a]
seqList [a]
xs) [a]
list

--------------------------------------------------
-- Advanced Conversions
--------------------------------------------------

{- | The type used for functions for 'wholeMap'.  See 'wholeMap' for details.
-}
newtype WholeFunc a b = WholeFunc ([a] -> (WholeFunc a b, [a], [b]))

{- | This is an enhanced version of the concatMap or map functions in
Data.List.

Unlike those functions, this one:

 * Can consume a varying number of elements from the input list during
   each iteration

 * Can arbitrarily decide when to stop processing data

 * Can return a varying number of elements to insert into the output list

 * Can actually switch processing functions mid-stream

 * Is not even restricted to processing the input list intact

The function used by wholeMap, of type 'WholeFunc', is repeatedly called
with the input list.  The function returns three things: the function
to call for the next iteration (if any), what remains of the input list,
and the list of output elements generated during this iteration.  The return
value of 'wholeMap' is the concatenation of the output element lists from
all iterations.

Processing stops when the remaining input list is empty.  An example
of a 'WholeFunc' is 'fixedWidth'. -}
wholeMap :: WholeFunc a b -> [a] -> [b]
wholeMap :: WholeFunc a b -> [a] -> [b]
wholeMap WholeFunc a b
_ [] = []              -- Empty input, empty output.
wholeMap (WholeFunc [a] -> (WholeFunc a b, [a], [b])
func) [a]
inplist =
    let (WholeFunc a b
nextfunc, [a]
nextlist, [b]
output) = [a] -> (WholeFunc a b, [a], [b])
func [a]
inplist
        in
        [b]
output [b] -> [b] -> [b]
forall a. [a] -> [a] -> [a]
++ WholeFunc a b -> [a] -> [b]
forall a b. WholeFunc a b -> [a] -> [b]
wholeMap WholeFunc a b
nextfunc [a]
nextlist

{- | A parser designed to process fixed-width input fields.  Use it with
'wholeMap'.

The Int list passed to this function is the list of the field widths desired
from the input.  The result is a list of those widths, if possible.  If any
of the input remains after processing this list, it is added on as the final
element in the result list.  If the input is less than the sum of the requested
widths, then the result list will be short the appropriate number of elements,
and its final element may be shorter than requested.

Examples:

>wholeMap (fixedWidth [1, 2, 3]) "1234567890"
> --> ["1","23","456","7890"]
>wholeMap (fixedWidth (repeat 2)) "123456789"
> --> ["12","34","56","78","9"]
>wholeMap (fixedWidth []) "123456789"
> --> ["123456789"]
>wholeMap (fixedWidth [5, 3, 6, 1]) "Hello, This is a test."
> --> ["Hello",", T","his is"," ","a test."]
-}
fixedWidth :: [Int] -> WholeFunc a [a]
fixedWidth :: [Int] -> WholeFunc a [a]
fixedWidth =
    ([a] -> (WholeFunc a [a], [a], [[a]])) -> WholeFunc a [a]
forall a b. ([a] -> (WholeFunc a b, [a], [b])) -> WholeFunc a b
WholeFunc (([a] -> (WholeFunc a [a], [a], [[a]])) -> WholeFunc a [a])
-> ([Int] -> [a] -> (WholeFunc a [a], [a], [[a]]))
-> [Int]
-> WholeFunc a [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [a] -> (WholeFunc a [a], [a], [[a]])
forall a a. [Int] -> [a] -> (WholeFunc a [a], [a], [[a]])
fixedWidthFunc
    where -- Empty input: Empty output, stop
          fixedWidthFunc :: [Int] -> [a] -> (WholeFunc a [a], [a], [[a]])
fixedWidthFunc [Int]
_ [] = (([Int] -> WholeFunc a [a]
forall a. [Int] -> WholeFunc a [a]
fixedWidth []), [], [])
          -- Empty length: Stop here.
          fixedWidthFunc [] [a]
x = (([Int] -> WholeFunc a [a]
forall a. [Int] -> WholeFunc a [a]
fixedWidth []), [], [[a]
x])
          -- Stuff to process: Do it.
          fixedWidthFunc (Int
len:[Int]
lenxs) [a]
input =
              ([Int] -> WholeFunc a [a]
forall a. [Int] -> WholeFunc a [a]
fixedWidth [Int]
lenxs, [a]
next, [[a]
this])
              where ([a]
this, [a]
next) = Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
len [a]
input

{- | Helps you pick out fixed-width components from a list.

Example:

>conv :: String -> (String,String)
>conv = runState $
>        do f3 <- grab 3
>           n2 <- grab 2
>           return $ f3 ++ "," ++ n2
>
>main = print $ conv "TestIng"

Prints:

>("Tes,tI","ng")
-}

grab :: Int -> State [a] [a]
grab :: Int -> State [a] [a]
grab Int
count =
    do [a]
g <- State [a] [a]
forall s (m :: * -> *). MonadState s m => m s
get
       ([a]
x, [a]
g') <- ([a], [a]) -> StateT [a] Identity ([a], [a])
forall (m :: * -> *) a. Monad m => a -> m a
return (([a], [a]) -> StateT [a] Identity ([a], [a]))
-> ([a], [a]) -> StateT [a] Identity ([a], [a])
forall a b. (a -> b) -> a -> b
$ Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
count [a]
g
       [a] -> StateT [a] Identity ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put [a]
g'
       [a] -> State [a] [a]
forall (m :: * -> *) a. Monad m => a -> m a
return [a]
x

{- | Similar to Data.List.elemIndex.  Instead of looking for one element in a
list, this function looks for the first occurance of a sublist in the list,
and returns the index of the first element of that occurance.  If there is no
such list, returns Nothing.

If the list to look for is the empty list, will return Just 0 regardless
of the content of the list to search.

Examples:

>subIndex "foo" "asdfoobar" -> Just 3
>subIndex "foo" [] -> Nothing
>subIndex "" [] -> Just 0
>subIndex "" "asdf" -> Just 0
>subIndex "test" "asdftestbartest" -> Just 4
>subIndex [(1::Int), 2] [0, 5, 3, 2, 1, 2, 4] -> Just 4
 -}
subIndex :: Eq a => [a] -> [a] -> Maybe Int
subIndex :: [a] -> [a] -> Maybe Int
subIndex [a]
substr [a]
str = ([a] -> Bool) -> [[a]] -> Maybe Int
forall a. (a -> Bool) -> [a] -> Maybe Int
findIndex ([a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf [a]
substr) ([a] -> [[a]]
forall a. [a] -> [[a]]
tails [a]
str)

{- | Given a list, returns a new list with all duplicate elements removed.
For example:

>uniq "Mississippi" -> "Misp"

You should not rely on this function necessarily preserving order, though
the current implementation happens to.

This function is not compatible with infinite lists.

This is presently an alias for 'Data.List.nub'.
 -}
uniq :: Eq a => [a] -> [a]
uniq :: [a] -> [a]
uniq = [a] -> [a]
forall a. Eq a => [a] -> [a]
nub

----- same as
--uniq (x:xs) = x : [y | y <- uniq xs, y /= x]