{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -Wno-orphans #-}

-- |
-- Linear versions of 'Data.List' functions.
--
-- This module only contains minimal amount of documentation; consult the
-- original "Data.List" module for more detailed information.
module Data.List.Linear
  ( -- * Basic functions
    (++),
    map,
    filter,
    NonLinear.head,
    uncons,
    NonLinear.tail,
    NonLinear.last,
    NonLinear.init,
    reverse,
    NonLinear.lookup,
    length,
    NonLinear.null,
    traverse',

    -- * Extracting sublists
    take,
    drop,
    splitAt,
    span,
    partition,
    takeWhile,
    dropWhile,
    NonLinear.find,
    intersperse,
    intercalate,
    transpose,

    -- * Folds
    foldl,
    foldl',
    foldl1,
    foldl1',
    foldr,
    foldr1,
    foldMap,
    foldMap',

    -- * Special folds
    concat,
    concatMap,
    and,
    or,
    any,
    all,
    sum,
    product,

    -- * Building lists
    scanl,
    scanl1,
    scanr,
    scanr1,
    repeat,
    replicate,
    cycle,
    iterate,
    unfoldr,

    -- * Ordered lists
    NonLinear.sort,
    NonLinear.sortOn,
    NonLinear.insert,

    -- * Zipping lists
    zip,
    zip',
    zip3,
    zipWith,
    zipWith',
    zipWith3,
    unzip,
    unzip3,
  )
where

import Data.Bool.Linear
import Data.Functor.Linear
import qualified Data.Functor.Linear as Data
import qualified Data.List as NonLinear
import Data.List.NonEmpty (NonEmpty ((:|)))
import Data.Monoid.Linear
import Data.Num.Linear
import Data.Unrestricted.Linear
import GHC.Stack
import Prelude.Linear.Internal
import qualified Unsafe.Linear as Unsafe
import Prelude (Either (..), Int, Maybe (..))
import qualified Prelude as Prelude

-- # Basic functions
--------------------------------------------------

(++) :: [a] %1 -> [a] %1 -> [a]
++ :: forall a. [a] %1 -> [a] %1 -> [a]
(++) = ([a] -> [a] -> [a]) %1 -> [a] %1 -> [a] %1 -> [a]
forall a b c (p :: Multiplicity) (q :: Multiplicity)
       (x :: Multiplicity) (y :: Multiplicity).
(a %p -> b %q -> c) %1 -> a %x -> b %y -> c
Unsafe.toLinear2 [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
(NonLinear.++)

infixr 5 ++ -- same fixity as base.++

map :: (a %1 -> b) -> [a] %1 -> [b]
map :: forall a b. (a %1 -> b) -> [a] %1 -> [b]
map = (a %1 -> b) -> [a] %1 -> [b]
forall (f :: * -> *) a b. Functor f => (a %1 -> b) -> f a %1 -> f b
fmap

-- | @filter p xs@ returns a list with elements satisfying the predicate.
--
-- See 'Data.Maybe.Linear.mapMaybe' if you do not want the 'Dupable' constraint.
filter :: Dupable a => (a %1 -> Bool) -> [a] %1 -> [a]
filter :: forall a. Dupable a => (a %1 -> Bool) -> [a] %1 -> [a]
filter a %1 -> Bool
_ [] = []
filter a %1 -> Bool
p (a
x : [a]
xs) =
  a %1 -> (a, a)
forall a. Dupable a => a %1 -> (a, a)
dup a
x (a, a) %1 -> ((a, a) %1 -> [a]) %1 -> [a]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \case
    (a
x', a
x'') ->
      if a %1 -> Bool
p a
x'
        then a
x'' a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: (a %1 -> Bool) -> [a] %1 -> [a]
forall a. Dupable a => (a %1 -> Bool) -> [a] %1 -> [a]
filter a %1 -> Bool
p [a]
xs
        else a
x'' a %1 -> [a] %1 -> [a]
forall a b. Consumable a => a %1 -> b %1 -> b
`lseq` (a %1 -> Bool) -> [a] %1 -> [a]
forall a. Dupable a => (a %1 -> Bool) -> [a] %1 -> [a]
filter a %1 -> Bool
p [a]
xs

uncons :: [a] %1 -> Maybe (a, [a])
uncons :: forall a. [a] %1 -> Maybe (a, [a])
uncons [] = Maybe (a, [a])
forall a. Maybe a
Nothing
uncons (a
x : [a]
xs) = (a, [a]) %1 -> Maybe (a, [a])
forall a. a -> Maybe a
Just (a
x, [a]
xs)

reverse :: [a] %1 -> [a]
reverse :: forall a. [a] %1 -> [a]
reverse = ([a] -> [a]) %1 -> [a] %1 -> [a]
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear [a] -> [a]
forall a. [a] -> [a]
NonLinear.reverse

-- | Return the length of the given list alongside with the list itself.
length :: [a] %1 -> (Ur Int, [a])
length :: forall a. [a] %1 -> (Ur Int, [a])
length = ([a] -> (Ur Int, [a])) %1 -> [a] %1 -> (Ur Int, [a])
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear (([a] -> (Ur Int, [a])) %1 -> [a] %1 -> (Ur Int, [a]))
-> ([a] -> (Ur Int, [a])) %1 -> [a] %1 -> (Ur Int, [a])
forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ \[a]
xs ->
  (Int -> Ur Int
forall a. a -> Ur a
Ur ([a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
NonLinear.length [a]
xs), [a]
xs)

-- We can only do this because of the fact that 'NonLinear.length'
-- does not inspect the elements.

--  'splitAt' @n xs@ returns a tuple where first element is @xs@ prefix of
-- length @n@ and second element is the remainder of the list.
splitAt :: Int -> [a] %1 -> ([a], [a])
splitAt :: forall a. Int -> [a] %1 -> ([a], [a])
splitAt Int
i = ([a] -> ([a], [a])) %1 -> [a] %1 -> ([a], [a])
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear (Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
Prelude.splitAt Int
i)

-- | 'span', applied to a predicate @p@ and a list @xs@, returns a tuple where
-- first element is longest prefix (possibly empty) of @xs@ of elements that
-- satisfy @p@ and second element is the remainder of the list.
span :: Dupable a => (a %1 -> Bool) -> [a] %1 -> ([a], [a])
span :: forall a. Dupable a => (a %1 -> Bool) -> [a] %1 -> ([a], [a])
span a %1 -> Bool
_ [] = ([], [])
span a %1 -> Bool
f (a
x : [a]
xs) =
  a %1 -> (a, a)
forall a. Dupable a => a %1 -> (a, a)
dup a
x (a, a) %1 -> ((a, a) %1 -> ([a], [a])) %1 -> ([a], [a])
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \case
    (a
x', a
x'') ->
      if a %1 -> Bool
f a
x'
        then (a %1 -> Bool) -> [a] %1 -> ([a], [a])
forall a. Dupable a => (a %1 -> Bool) -> [a] %1 -> ([a], [a])
span a %1 -> Bool
f [a]
xs ([a], [a]) %1 -> (([a], [a]) %1 -> ([a], [a])) %1 -> ([a], [a])
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \case ([a]
ts, [a]
fs) -> (a
x'' a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: [a]
ts, [a]
fs)
        else ([a
x''], [a]
xs)

-- The partition function takes a predicate a list and returns the
-- pair of lists of elements which do and do not satisfy the predicate,
-- respectively.
partition :: Dupable a => (a %1 -> Bool) -> [a] %1 -> ([a], [a])
partition :: forall a. Dupable a => (a %1 -> Bool) -> [a] %1 -> ([a], [a])
partition a %1 -> Bool
p ([a]
xs :: [a]) = (a %1 -> ([a], [a]) %1 -> ([a], [a]))
-> ([a], [a]) %1 -> [a] %1 -> ([a], [a])
forall a b. (a %1 -> b %1 -> b) -> b %1 -> [a] %1 -> b
foldr a %1 -> ([a], [a]) %1 -> ([a], [a])
select ([], []) [a]
xs
  where
    select :: a %1 -> ([a], [a]) %1 -> ([a], [a])
    select :: a %1 -> ([a], [a]) %1 -> ([a], [a])
select a
x ([a]
ts, [a]
fs) =
      a %1 -> (a, a)
forall a. Dupable a => a %1 -> (a, a)
dup2 a
x (a, a) %1 -> ((a, a) %1 -> ([a], [a])) %1 -> ([a], [a])
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \(a
x', a
x'') ->
        if a %1 -> Bool
p a
x'
          then (a
x'' a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: [a]
ts, [a]
fs)
          else ([a]
ts, a
x'' a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: [a]
fs)

-- | __NOTE__: This does not short-circuit and always traverses the
-- entire list to consume the rest of the elements.
takeWhile :: Dupable a => (a %1 -> Bool) -> [a] %1 -> [a]
takeWhile :: forall a. Dupable a => (a %1 -> Bool) -> [a] %1 -> [a]
takeWhile a %1 -> Bool
_ [] = []
takeWhile a %1 -> Bool
p (a
x : [a]
xs) =
  a %1 -> (a, a)
forall a. Dupable a => a %1 -> (a, a)
dup2 a
x (a, a) %1 -> ((a, a) %1 -> [a]) %1 -> [a]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \(a
x', a
x'') ->
    if a %1 -> Bool
p a
x'
      then a
x'' a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: (a %1 -> Bool) -> [a] %1 -> [a]
forall a. Dupable a => (a %1 -> Bool) -> [a] %1 -> [a]
takeWhile a %1 -> Bool
p [a]
xs
      else (a
x'', [a]
xs) (a, [a]) %1 -> [a] %1 -> [a]
forall a b. Consumable a => a %1 -> b %1 -> b
`lseq` []

dropWhile :: Dupable a => (a %1 -> Bool) -> [a] %1 -> [a]
dropWhile :: forall a. Dupable a => (a %1 -> Bool) -> [a] %1 -> [a]
dropWhile a %1 -> Bool
_ [] = []
dropWhile a %1 -> Bool
p (a
x : [a]
xs) =
  a %1 -> (a, a)
forall a. Dupable a => a %1 -> (a, a)
dup2 a
x (a, a) %1 -> ((a, a) %1 -> [a]) %1 -> [a]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \(a
x', a
x'') ->
    if a %1 -> Bool
p a
x'
      then a
x'' a %1 -> [a] %1 -> [a]
forall a b. Consumable a => a %1 -> b %1 -> b
`lseq` (a %1 -> Bool) -> [a] %1 -> [a]
forall a. Dupable a => (a %1 -> Bool) -> [a] %1 -> [a]
dropWhile a %1 -> Bool
p [a]
xs
      else a
x'' a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: [a]
xs

-- | __NOTE__: This does not short-circuit and always traverses the
-- entire list to consume the rest of the elements.
take :: Consumable a => Int -> [a] %1 -> [a]
take :: forall a. Consumable a => Int -> [a] %1 -> [a]
take Int
_ [] = []
take Int
i (a
x : [a]
xs)
  | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
Prelude.< Int
0 = (a
x, [a]
xs) (a, [a]) %1 -> [a] %1 -> [a]
forall a b. Consumable a => a %1 -> b %1 -> b
`lseq` []
  | Bool
otherwise = a
x a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: Int -> [a] %1 -> [a]
forall a. Consumable a => Int -> [a] %1 -> [a]
take (Int
i Int %1 -> Int %1 -> Int
forall a. AdditiveGroup a => a %1 -> a %1 -> a
- Int
1) [a]
xs

drop :: Consumable a => Int -> [a] %1 -> [a]
drop :: forall a. Consumable a => Int -> [a] %1 -> [a]
drop Int
_ [] = []
drop Int
i (a
x : [a]
xs)
  | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
Prelude.< Int
0 = a
x a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: [a]
xs
  | Bool
otherwise = a
x a %1 -> [a] %1 -> [a]
forall a b. Consumable a => a %1 -> b %1 -> b
`lseq` Int -> [a] %1 -> [a]
forall a. Consumable a => Int -> [a] %1 -> [a]
drop (Int
i Int %1 -> Int %1 -> Int
forall a. AdditiveGroup a => a %1 -> a %1 -> a
- Int
1) [a]
xs

-- | The intersperse function takes an element and a list and
-- `intersperses' that element between the elements of the list.
intersperse :: a -> [a] %1 -> [a]
intersperse :: forall a. a -> [a] %1 -> [a]
intersperse a
sep = ([a] -> [a]) %1 -> [a] %1 -> [a]
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear (a -> [a] -> [a]
forall a. a -> [a] -> [a]
NonLinear.intersperse a
sep)

-- | @intercalate xs xss@ is equivalent to @(concat (intersperse xs
-- xss))@. It inserts the list xs in between the lists in xss and
-- concatenates the result.
intercalate :: [a] -> [[a]] %1 -> [a]
intercalate :: forall a. [a] -> [[a]] %1 -> [a]
intercalate [a]
sep = ([[a]] -> [a]) %1 -> [[a]] %1 -> [a]
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear ([a] -> [[a]] -> [a]
forall a. [a] -> [[a]] -> [a]
NonLinear.intercalate [a]
sep)

-- | The transpose function transposes the rows and columns of its argument.
transpose :: [[a]] %1 -> [[a]]
transpose :: forall a. [[a]] %1 -> [[a]]
transpose = ([[a]] -> [[a]]) %1 -> [[a]] %1 -> [[a]]
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear [[a]] -> [[a]]
forall a. [[a]] -> [[a]]
NonLinear.transpose

traverse' :: Data.Applicative f => (a %1 -> f b) -> [a] %1 -> f [b]
traverse' :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> [a] %1 -> f [b]
traverse' a %1 -> f b
_ [] = [b] -> f [b]
forall (f :: * -> *) a. Applicative f => a -> f a
Data.pure []
traverse' a %1 -> f b
f (a
a : [a]
as) = (:) (b %1 -> [b] %1 -> [b]) -> f b %1 -> f ([b] %1 -> [b])
forall (f :: * -> *) a b. Functor f => (a %1 -> b) -> f a %1 -> f b
<$> a %1 -> f b
f a
a f ([b] %1 -> [b]) %1 -> f [b] %1 -> f [b]
forall (f :: * -> *) a b.
Applicative f =>
f (a %1 -> b) %1 -> f a %1 -> f b
<*> (a %1 -> f b) -> [a] %1 -> f [b]
forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> [a] %1 -> f [b]
traverse' a %1 -> f b
f [a]
as

-- # Folds
--------------------------------------------------

foldr :: (a %1 -> b %1 -> b) -> b %1 -> [a] %1 -> b
foldr :: forall a b. (a %1 -> b %1 -> b) -> b %1 -> [a] %1 -> b
foldr a %1 -> b %1 -> b
f = (b -> [a] -> b) %1 -> b %1 -> [a] %1 -> b
forall a b c (p :: Multiplicity) (q :: Multiplicity)
       (x :: Multiplicity) (y :: Multiplicity).
(a %p -> b %q -> c) %1 -> a %x -> b %y -> c
Unsafe.toLinear2 ((a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
NonLinear.foldr (\a
a b
b -> a %1 -> b %1 -> b
f a
a b
b))

foldr1 :: HasCallStack => (a %1 -> a %1 -> a) -> [a] %1 -> a
foldr1 :: forall a. HasCallStack => (a %1 -> a %1 -> a) -> [a] %1 -> a
foldr1 a %1 -> a %1 -> a
f = ([a] -> a) %1 -> [a] %1 -> a
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear ((a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
NonLinear.foldr1 (\a
a a
b -> a %1 -> a %1 -> a
f a
a a
b))

foldl :: (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b
foldl :: forall b a. (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b
foldl b %1 -> a %1 -> b
f = (b -> [a] -> b) %1 -> b %1 -> [a] %1 -> b
forall a b c (p :: Multiplicity) (q :: Multiplicity)
       (x :: Multiplicity) (y :: Multiplicity).
(a %p -> b %q -> c) %1 -> a %x -> b %y -> c
Unsafe.toLinear2 ((b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
NonLinear.foldl (\b
b a
a -> b %1 -> a %1 -> b
f b
b a
a))

foldl' :: (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b
foldl' :: forall b a. (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b
foldl' b %1 -> a %1 -> b
f = (b -> [a] -> b) %1 -> b %1 -> [a] %1 -> b
forall a b c (p :: Multiplicity) (q :: Multiplicity)
       (x :: Multiplicity) (y :: Multiplicity).
(a %p -> b %q -> c) %1 -> a %x -> b %y -> c
Unsafe.toLinear2 ((b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
NonLinear.foldl' (\b
b a
a -> b %1 -> a %1 -> b
f b
b a
a))

foldl1 :: HasCallStack => (a %1 -> a %1 -> a) -> [a] %1 -> a
foldl1 :: forall a. HasCallStack => (a %1 -> a %1 -> a) -> [a] %1 -> a
foldl1 a %1 -> a %1 -> a
f = ([a] -> a) %1 -> [a] %1 -> a
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear ((a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
NonLinear.foldl1 (\a
a a
b -> a %1 -> a %1 -> a
f a
a a
b))

foldl1' :: HasCallStack => (a %1 -> a %1 -> a) -> [a] %1 -> a
foldl1' :: forall a. HasCallStack => (a %1 -> a %1 -> a) -> [a] %1 -> a
foldl1' a %1 -> a %1 -> a
f = ([a] -> a) %1 -> [a] %1 -> a
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear ((a -> a -> a) -> [a] -> a
forall a. (a -> a -> a) -> [a] -> a
NonLinear.foldl1' (\a
a a
b -> a %1 -> a %1 -> a
f a
a a
b))

-- | Map each element of the structure to a monoid,
-- and combine the results.
foldMap :: Monoid m => (a %1 -> m) -> [a] %1 -> m
foldMap :: forall m a. Monoid m => (a %1 -> m) -> [a] %1 -> m
foldMap a %1 -> m
f = (a %1 -> m %1 -> m) -> m %1 -> [a] %1 -> m
forall a b. (a %1 -> b %1 -> b) -> b %1 -> [a] %1 -> b
foldr (m %1 -> m %1 -> m
forall a. Semigroup a => a %1 -> a %1 -> a
(<>) (m %1 -> m %1 -> m) -> (a %1 -> m) -> a %1 -> m %1 -> m
forall b c a (q :: Multiplicity) (m :: Multiplicity)
       (n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. a %1 -> m
f) m
forall a. Monoid a => a
mempty

-- | A variant of 'foldMap' that is strict in the accumulator.
foldMap' :: Monoid m => (a %1 -> m) -> [a] %1 -> m
foldMap' :: forall m a. Monoid m => (a %1 -> m) -> [a] %1 -> m
foldMap' a %1 -> m
f = (m %1 -> a %1 -> m) -> m %1 -> [a] %1 -> m
forall b a. (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b
foldl' (\m
acc a
a -> m
acc m %1 -> m %1 -> m
forall a. Semigroup a => a %1 -> a %1 -> a
<> a %1 -> m
f a
a) m
forall a. Monoid a => a
mempty

concat :: [[a]] %1 -> [a]
concat :: forall a. [[a]] %1 -> [a]
concat = ([[a]] -> [a]) %1 -> [[a]] %1 -> [a]
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear [[a]] -> [a]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
NonLinear.concat

concatMap :: (a %1 -> [b]) -> [a] %1 -> [b]
concatMap :: forall a b. (a %1 -> [b]) -> [a] %1 -> [b]
concatMap a %1 -> [b]
f = ([a] -> [b]) %1 -> [a] %1 -> [b]
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear ((a -> [b]) -> [a] -> [b]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
NonLinear.concatMap ((a %1 -> [b]) %1 -> a -> [b]
forall a b. (a %1 -> b) %1 -> a -> b
forget a %1 -> [b]
f))

sum :: AddIdentity a => [a] %1 -> a
sum :: forall a. AddIdentity a => [a] %1 -> a
sum = (a %1 -> a %1 -> a) -> a %1 -> [a] %1 -> a
forall b a. (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b
foldl' a %1 -> a %1 -> a
forall a. Additive a => a %1 -> a %1 -> a
(+) a
forall a. AddIdentity a => a
zero

product :: MultIdentity a => [a] %1 -> a
product :: forall a. MultIdentity a => [a] %1 -> a
product = (a %1 -> a %1 -> a) -> a %1 -> [a] %1 -> a
forall b a. (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b
foldl' a %1 -> a %1 -> a
forall a. Multiplicative a => a %1 -> a %1 -> a
(*) a
forall a. MultIdentity a => a
one

-- | __NOTE:__ This does not short-circuit, and always consumes the
-- entire container.
any :: (a %1 -> Bool) -> [a] %1 -> Bool
any :: forall a. (a %1 -> Bool) -> [a] %1 -> Bool
any a %1 -> Bool
p = (Bool %1 -> a %1 -> Bool) -> Bool %1 -> [a] %1 -> Bool
forall b a. (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b
foldl' (\Bool
b a
a -> Bool
b Bool %1 -> Bool %1 -> Bool
|| a %1 -> Bool
p a
a) Bool
False

-- | __NOTE:__ This does not short-circuit, and always consumes the
-- entire container.
all :: (a %1 -> Bool) -> [a] %1 -> Bool
all :: forall a. (a %1 -> Bool) -> [a] %1 -> Bool
all a %1 -> Bool
p = (Bool %1 -> a %1 -> Bool) -> Bool %1 -> [a] %1 -> Bool
forall b a. (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b
foldl' (\Bool
b a
a -> Bool
b Bool %1 -> Bool %1 -> Bool
&& a %1 -> Bool
p a
a) Bool
True

-- | __NOTE:__ This does not short-circuit, and always consumes the
-- entire container.
and :: [Bool] %1 -> Bool
and :: [Bool] %1 -> Bool
and = (Bool %1 -> Bool %1 -> Bool) -> Bool %1 -> [Bool] %1 -> Bool
forall b a. (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b
foldl' Bool %1 -> Bool %1 -> Bool
(&&) Bool
True

-- | __NOTE:__ This does not short-circuit, and always consumes the
-- entire container.
or :: [Bool] %1 -> Bool
or :: [Bool] %1 -> Bool
or = (Bool %1 -> Bool %1 -> Bool) -> Bool %1 -> [Bool] %1 -> Bool
forall b a. (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b
foldl' Bool %1 -> Bool %1 -> Bool
(||) Bool
False

-- # Building Lists
--------------------------------------------------

iterate :: Dupable a => (a %1 -> a) -> a %1 -> [a]
iterate :: forall a. Dupable a => (a %1 -> a) -> a %1 -> [a]
iterate a %1 -> a
f a
a =
  a %1 -> (a, a)
forall a. Dupable a => a %1 -> (a, a)
dup2 a
a (a, a) %1 -> ((a, a) %1 -> [a]) -> [a]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \(a
a', a
a'') ->
    a
a' a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: (a %1 -> a) -> a %1 -> [a]
forall a. Dupable a => (a %1 -> a) -> a %1 -> [a]
iterate a %1 -> a
f (a %1 -> a
f a
a'')

repeat :: Dupable a => a %1 -> [a]
repeat :: forall a. Dupable a => a %1 -> [a]
repeat = (a %1 -> a) -> a %1 -> [a]
forall a. Dupable a => (a %1 -> a) -> a %1 -> [a]
iterate a %1 -> a
forall a (q :: Multiplicity). a %q -> a
id

cycle :: (HasCallStack, Dupable a) => [a] %1 -> [a]
cycle :: forall a. (HasCallStack, Dupable a) => [a] %1 -> [a]
cycle [] = [Char] -> [a]
forall a. HasCallStack => [Char] -> a
Prelude.error [Char]
"cycle: empty list"
cycle [a]
xs = [a] %1 -> ([a], [a])
forall a. Dupable a => a %1 -> (a, a)
dup2 [a]
xs ([a], [a]) %1 -> (([a], [a]) %1 -> [a]) -> [a]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \([a]
xs', [a]
xs'') -> [a]
xs' [a] %1 -> [a] %1 -> [a]
forall a. [a] %1 -> [a] %1 -> [a]
++ [a] %1 -> [a]
forall a. (HasCallStack, Dupable a) => [a] %1 -> [a]
cycle [a]
xs''

scanl :: Dupable b => (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> [b]
scanl :: forall b a.
Dupable b =>
(b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> [b]
scanl b %1 -> a %1 -> b
_ b
b [] = [b
b]
scanl b %1 -> a %1 -> b
f b
b (a
x : [a]
xs) = b %1 -> (b, b)
forall a. Dupable a => a %1 -> (a, a)
dup2 b
b (b, b) %1 -> ((b, b) %1 -> [b]) %1 -> [b]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \(b
b', b
b'') -> b
b' b %1 -> [b] %1 -> [b]
forall a. a -> [a] -> [a]
: (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> [b]
forall b a.
Dupable b =>
(b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> [b]
scanl b %1 -> a %1 -> b
f (b %1 -> a %1 -> b
f b
b'' a
x) [a]
xs

scanl1 :: Dupable a => (a %1 -> a %1 -> a) -> [a] %1 -> [a]
scanl1 :: forall a. Dupable a => (a %1 -> a %1 -> a) -> [a] %1 -> [a]
scanl1 a %1 -> a %1 -> a
_ [] = []
scanl1 a %1 -> a %1 -> a
f (a
x : [a]
xs) = (a %1 -> a %1 -> a) -> a %1 -> [a] %1 -> [a]
forall b a.
Dupable b =>
(b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> [b]
scanl a %1 -> a %1 -> a
f a
x [a]
xs

scanr :: Dupable b => (a %1 -> b %1 -> b) -> b %1 -> [a] %1 -> [b]
scanr :: forall b a.
Dupable b =>
(a %1 -> b %1 -> b) -> b %1 -> [a] %1 -> [b]
scanr a %1 -> b %1 -> b
_ b
b [] = [b
b]
scanr a %1 -> b %1 -> b
f b
b (a
a : [a]
as) =
  (a %1 -> b %1 -> b) -> b %1 -> [a] %1 -> [b]
forall b a.
Dupable b =>
(a %1 -> b %1 -> b) -> b %1 -> [a] %1 -> [b]
scanr a %1 -> b %1 -> b
f b
b [a]
as [b] %1 -> ([b] %1 -> [b]) %1 -> [b]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \case
    (b
b' : [b]
bs') ->
      b %1 -> (b, b)
forall a. Dupable a => a %1 -> (a, a)
dup2 b
b' (b, b) %1 -> ((b, b) %1 -> [b]) %1 -> [b]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \(b
b'', b
b''') ->
        a %1 -> b %1 -> b
f a
a b
b'' b %1 -> [b] %1 -> [b]
forall a. a -> [a] -> [a]
: b
b''' b %1 -> [b] %1 -> [b]
forall a. a -> [a] -> [a]
: [b]
bs'
    [] ->
      -- this branch is impossible since scanr never returns an empty list.
      [Char] -> a %1 -> [b]
forall a. HasCallStack => [Char] -> a
Prelude.error [Char]
"impossible" a
a

scanr1 :: Dupable a => (a %1 -> a %1 -> a) -> [a] %1 -> [a]
scanr1 :: forall a. Dupable a => (a %1 -> a %1 -> a) -> [a] %1 -> [a]
scanr1 a %1 -> a %1 -> a
_ [] = []
scanr1 a %1 -> a %1 -> a
_ [a
a] = [a
a]
scanr1 a %1 -> a %1 -> a
f (a
a : [a]
as) =
  (a %1 -> a %1 -> a) -> [a] %1 -> [a]
forall a. Dupable a => (a %1 -> a %1 -> a) -> [a] %1 -> [a]
scanr1 a %1 -> a %1 -> a
f [a]
as [a] %1 -> ([a] %1 -> [a]) %1 -> [a]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \case
    (a
a' : [a]
as') ->
      a %1 -> (a, a)
forall a. Dupable a => a %1 -> (a, a)
dup2 a
a' (a, a) %1 -> ((a, a) %1 -> [a]) %1 -> [a]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \(a
a'', a
a''') ->
        a %1 -> a %1 -> a
f a
a a
a'' a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: a
a''' a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: [a]
as'
    [] ->
      -- this branch is impossible since we know that the 'scanr1' result will
      -- be non-empty since 'as' is also non-empty.
      [Char] -> a %1 -> [a]
forall a. HasCallStack => [Char] -> a
Prelude.error [Char]
"impossible" a
a

replicate :: Dupable a => Int -> a %1 -> [a]
replicate :: forall a. Dupable a => Int -> a %1 -> [a]
replicate Int
i a
a
  | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
Prelude.< Int
1 = a
a a %1 -> [a] %1 -> [a]
forall a b. Consumable a => a %1 -> b %1 -> b
`lseq` []
  | Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
Prelude.== Int
1 = [a
a]
  | Bool
otherwise = a %1 -> (a, a)
forall a. Dupable a => a %1 -> (a, a)
dup2 a
a (a, a) %1 -> ((a, a) %1 -> [a]) -> [a]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \(a
a', a
a'') -> a
a' a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: Int -> a %1 -> [a]
forall a. Dupable a => Int -> a %1 -> [a]
replicate (Int
i Int %1 -> Int %1 -> Int
forall a. AdditiveGroup a => a %1 -> a %1 -> a
- Int
1) a
a''

unfoldr :: (b %1 -> Maybe (a, b)) -> b %1 -> [a]
unfoldr :: forall b a. (b %1 -> Maybe (a, b)) -> b %1 -> [a]
unfoldr b %1 -> Maybe (a, b)
f = (b -> [a]) %1 -> b %1 -> [a]
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear ((b -> Maybe (a, b)) -> b -> [a]
forall b a. (b -> Maybe (a, b)) -> b -> [a]
NonLinear.unfoldr ((b %1 -> Maybe (a, b)) %1 -> b -> Maybe (a, b)
forall a b. (a %1 -> b) %1 -> a -> b
forget b %1 -> Maybe (a, b)
f))

-- # Zipping and unzipping lists
--------------------------------------------------

zip :: (Consumable a, Consumable b) => [a] %1 -> [b] %1 -> [(a, b)]
zip :: forall a b.
(Consumable a, Consumable b) =>
[a] %1 -> [b] %1 -> [(a, b)]
zip = (a %1 -> b %1 -> (a, b)) -> [a] %1 -> [b] %1 -> [(a, b)]
forall a b c.
(Consumable a, Consumable b) =>
(a %1 -> b %1 -> c) -> [a] %1 -> [b] %1 -> [c]
zipWith (,)

-- | Same as 'zip', but returns the leftovers instead of consuming them.
zip' :: [a] %1 -> [b] %1 -> ([(a, b)], Maybe (Either (NonEmpty a) (NonEmpty b)))
zip' :: forall a b.
[a]
%1 -> [b]
%1 -> ([(a, b)], Maybe (Either (NonEmpty a) (NonEmpty b)))
zip' = (a %1 -> b %1 -> (a, b))
-> [a]
%1 -> [b]
%1 -> ([(a, b)], Maybe (Either (NonEmpty a) (NonEmpty b)))
forall a b c.
(a %1 -> b %1 -> c)
-> [a]
%1 -> [b]
%1 -> ([c], Maybe (Either (NonEmpty a) (NonEmpty b)))
zipWith' (,)

zip3 :: (Consumable a, Consumable b, Consumable c) => [a] %1 -> [b] %1 -> [c] %1 -> [(a, b, c)]
zip3 :: forall a b c.
(Consumable a, Consumable b, Consumable c) =>
[a] %1 -> [b] %1 -> [c] %1 -> [(a, b, c)]
zip3 = (a %1 -> b %1 -> c %1 -> (a, b, c))
-> [a] %1 -> [b] %1 -> [c] %1 -> [(a, b, c)]
forall a b c d.
(Consumable a, Consumable b, Consumable c) =>
(a %1 -> b %1 -> c %1 -> d) -> [a] %1 -> [b] %1 -> [c] %1 -> [d]
zipWith3 (,,)

zipWith :: (Consumable a, Consumable b) => (a %1 -> b %1 -> c) -> [a] %1 -> [b] %1 -> [c]
zipWith :: forall a b c.
(Consumable a, Consumable b) =>
(a %1 -> b %1 -> c) -> [a] %1 -> [b] %1 -> [c]
zipWith a %1 -> b %1 -> c
f [a]
xs [b]
ys =
  (a %1 -> b %1 -> c)
-> [a]
%1 -> [b]
%1 -> ([c], Maybe (Either (NonEmpty a) (NonEmpty b)))
forall a b c.
(a %1 -> b %1 -> c)
-> [a]
%1 -> [b]
%1 -> ([c], Maybe (Either (NonEmpty a) (NonEmpty b)))
zipWith' a %1 -> b %1 -> c
f [a]
xs [b]
ys ([c], Maybe (Either (NonEmpty a) (NonEmpty b)))
%1 -> (([c], Maybe (Either (NonEmpty a) (NonEmpty b))) %1 -> [c])
-> [c]
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \([c]
ret, Maybe (Either (NonEmpty a) (NonEmpty b))
leftovers) ->
    Maybe (Either (NonEmpty a) (NonEmpty b))
leftovers Maybe (Either (NonEmpty a) (NonEmpty b)) %1 -> [c] %1 -> [c]
forall a b. Consumable a => a %1 -> b %1 -> b
`lseq` [c]
ret

-- | Same as 'zipWith', but returns the leftovers instead of consuming them.
zipWith' :: (a %1 -> b %1 -> c) -> [a] %1 -> [b] %1 -> ([c], Maybe (Either (NonEmpty a) (NonEmpty b)))
zipWith' :: forall a b c.
(a %1 -> b %1 -> c)
-> [a]
%1 -> [b]
%1 -> ([c], Maybe (Either (NonEmpty a) (NonEmpty b)))
zipWith' a %1 -> b %1 -> c
_ [] [] = ([], Maybe (Either (NonEmpty a) (NonEmpty b))
forall a. Maybe a
Nothing)
zipWith' a %1 -> b %1 -> c
_ (a
a : [a]
as) [] = ([], Either (NonEmpty a) (NonEmpty b)
%1 -> Maybe (Either (NonEmpty a) (NonEmpty b))
forall a. a -> Maybe a
Just (NonEmpty a %1 -> Either (NonEmpty a) (NonEmpty b)
forall a b. a -> Either a b
Left (a
a a %1 -> [a] %1 -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
as)))
zipWith' a %1 -> b %1 -> c
_ [] (b
b : [b]
bs) = ([], Either (NonEmpty a) (NonEmpty b)
%1 -> Maybe (Either (NonEmpty a) (NonEmpty b))
forall a. a -> Maybe a
Just (NonEmpty b %1 -> Either (NonEmpty a) (NonEmpty b)
forall a b. b -> Either a b
Right (b
b b %1 -> [b] %1 -> NonEmpty b
forall a. a -> [a] -> NonEmpty a
:| [b]
bs)))
zipWith' a %1 -> b %1 -> c
f (a
a : [a]
as) (b
b : [b]
bs) =
  (a %1 -> b %1 -> c)
-> [a]
%1 -> [b]
%1 -> ([c], Maybe (Either (NonEmpty a) (NonEmpty b)))
forall a b c.
(a %1 -> b %1 -> c)
-> [a]
%1 -> [b]
%1 -> ([c], Maybe (Either (NonEmpty a) (NonEmpty b)))
zipWith' a %1 -> b %1 -> c
f [a]
as [b]
bs ([c], Maybe (Either (NonEmpty a) (NonEmpty b)))
%1 -> (([c], Maybe (Either (NonEmpty a) (NonEmpty b)))
       %1 -> ([c], Maybe (Either (NonEmpty a) (NonEmpty b))))
%1 -> ([c], Maybe (Either (NonEmpty a) (NonEmpty b)))
forall a b (p :: Multiplicity) (q :: Multiplicity).
a %p -> (a %p -> b) %q -> b
& \case
    ([c]
cs, Maybe (Either (NonEmpty a) (NonEmpty b))
rest) -> (a %1 -> b %1 -> c
f a
a b
b c %1 -> [c] %1 -> [c]
forall a. a -> [a] -> [a]
: [c]
cs, Maybe (Either (NonEmpty a) (NonEmpty b))
rest)

zipWith3 :: forall a b c d. (Consumable a, Consumable b, Consumable c) => (a %1 -> b %1 -> c %1 -> d) -> [a] %1 -> [b] %1 -> [c] %1 -> [d]
zipWith3 :: forall a b c d.
(Consumable a, Consumable b, Consumable c) =>
(a %1 -> b %1 -> c %1 -> d) -> [a] %1 -> [b] %1 -> [c] %1 -> [d]
zipWith3 a %1 -> b %1 -> c %1 -> d
_ [] [b]
ys [c]
zs = ([b]
ys, [c]
zs) ([b], [c]) %1 -> [d] %1 -> [d]
forall a b. Consumable a => a %1 -> b %1 -> b
`lseq` []
zipWith3 a %1 -> b %1 -> c %1 -> d
_ [a]
xs [] [c]
zs = ([a]
xs, [c]
zs) ([a], [c]) %1 -> [d] %1 -> [d]
forall a b. Consumable a => a %1 -> b %1 -> b
`lseq` []
zipWith3 a %1 -> b %1 -> c %1 -> d
_ [a]
xs [b]
ys [] = ([a]
xs, [b]
ys) ([a], [b]) %1 -> [d] %1 -> [d]
forall a b. Consumable a => a %1 -> b %1 -> b
`lseq` []
zipWith3 a %1 -> b %1 -> c %1 -> d
f (a
x : [a]
xs) (b
y : [b]
ys) (c
z : [c]
zs) = a %1 -> b %1 -> c %1 -> d
f a
x b
y c
z d %1 -> [d] %1 -> [d]
forall a. a -> [a] -> [a]
: (a %1 -> b %1 -> c %1 -> d) -> [a] %1 -> [b] %1 -> [c] %1 -> [d]
forall a b c d.
(Consumable a, Consumable b, Consumable c) =>
(a %1 -> b %1 -> c %1 -> d) -> [a] %1 -> [b] %1 -> [c] %1 -> [d]
zipWith3 a %1 -> b %1 -> c %1 -> d
f [a]
xs [b]
ys [c]
zs

unzip :: [(a, b)] %1 -> ([a], [b])
unzip :: forall a b. [(a, b)] %1 -> ([a], [b])
unzip = ([(a, b)] -> ([a], [b])) %1 -> [(a, b)] %1 -> ([a], [b])
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear [(a, b)] -> ([a], [b])
forall a b. [(a, b)] -> ([a], [b])
NonLinear.unzip

unzip3 :: [(a, b, c)] %1 -> ([a], [b], [c])
unzip3 :: forall a b c. [(a, b, c)] %1 -> ([a], [b], [c])
unzip3 = ([(a, b, c)] -> ([a], [b], [c]))
%1 -> [(a, b, c)] %1 -> ([a], [b], [c])
forall a b (p :: Multiplicity) (x :: Multiplicity).
(a %p -> b) %1 -> a %x -> b
Unsafe.toLinear [(a, b, c)] -> ([a], [b], [c])
forall a b c. [(a, b, c)] -> ([a], [b], [c])
NonLinear.unzip3

-- # Instances
--------------------------------------------------

instance Semigroup (NonEmpty a) where
  (a
x :| [a]
xs) <> :: NonEmpty a %1 -> NonEmpty a %1 -> NonEmpty a
<> (a
y :| [a]
ys) = a
x a %1 -> [a] %1 -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| ([a]
xs [a] %1 -> [a] %1 -> [a]
forall a. [a] %1 -> [a] %1 -> [a]
++ (a
y a %1 -> [a] %1 -> [a]
forall a. a -> [a] -> [a]
: [a]
ys))

instance Semigroup [a] where
  <> :: [a] %1 -> [a] %1 -> [a]
(<>) = [a] %1 -> [a] %1 -> [a]
forall a. [a] %1 -> [a] %1 -> [a]
(++)
  {-# INLINE (<>) #-}

instance Monoid [a] where
  mempty :: [a]
mempty = []