{-# LANGUAGE UndecidableInstances #-}

-- |
-- Module      : Streamly.Internal.Data.List
-- Copyright   : (c) 2018 Composewell Technologies
--
-- License     : BSD3
-- Maintainer  : streamly@composewell.com
-- Stability   : pre-release
-- Portability : GHC
--
-- Lists are just a special case of monadic streams. The stream type @SerialT
-- Identity a@ can be used as a replacement for @[a]@.  The 'List' type in this
-- module is just a newtype wrapper around @SerialT Identity@ for better type
-- inference when using the 'OverloadedLists' GHC extension. @List a@ provides
-- better performance compared to @[a]@. Standard list, string and list
-- comprehension syntax can be used with the 'List' type by enabling
-- 'OverloadedLists', 'OverloadedStrings' and 'MonadComprehensions' GHC
-- extensions.  There would be a slight difference in the 'Show' and 'Read'
-- strings of streamly list as compared to regular lists.
--
-- Conversion to stream types is free, any stream combinator can be used on
-- lists by converting them to streams.  However, for convenience, this module
-- provides combinators that work directly on the 'List' type.
--
--
-- @
-- List $ S.map (+ 1) $ toSerial (1 \`Cons\` Nil)
-- @
--
-- To convert a 'List' to regular lists, you can use any of the following:
--
-- * @toList . toSerial@ and @toSerial . fromList@
-- * 'Data.Foldable.toList' from "Data.Foldable"
-- * 'GHC.Exts.toList' and 'GHC.Exts.fromList' from 'IsList' in "GHC.Exts"
--
-- If you have made use of 'Nil' and 'Cons' constructors in the code and you
-- want to replace streamly lists with standard lists, all you need to do is
-- import these definitions:
--
-- @
-- type List = []
-- pattern Nil <- [] where Nil = []
-- pattern Cons x xs = x : xs
-- infixr 5 `Cons`
-- {-\# COMPLETE Cons, Nil #-}
-- @
--
-- See <src/docs/streamly-vs-lists.md> for more details and
-- <src/test/PureStreams.hs> for comprehensive usage examples.
--
module Streamly.Internal.Data.List
    (
    List (.., Nil, Cons)

    -- XXX we may want to use rebindable syntax for variants instead of using
    -- different types (applicative do and apWith).
    , ZipList (..)
    , fromZipList
    , toZipList
    )
where

import Control.Arrow (second)
import Control.DeepSeq (NFData(..))
#if MIN_VERSION_deepseq(1,4,3)
import Control.DeepSeq (NFData1(..))
#endif
import Data.Functor.Identity (Identity, runIdentity)
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup (Semigroup(..))
#endif
import GHC.Exts (IsList(..), IsString(..))

import Streamly.Internal.Data.Stream.Serial (SerialT(..))
import Streamly.Internal.Data.Stream.Zip (ZipSerialM(..))

import qualified Streamly.Internal.Data.Stream.Serial as Serial
import qualified Streamly.Internal.Data.Stream.StreamK.Type as K

-- We implement list as a newtype instead of a type synonym to make type
-- inference easier when using -XOverloadedLists and -XOverloadedStrings. When
-- using a stream type the programmer needs to specify the Monad otherwise the
-- type remains ambiguous.
--
-- XXX once we separate consM from IsStream or remove the MonadIO and
-- MonadBaseControlIO dependency from it, then we can make this an instance of
-- IsStream and use the regular polymorphic functions on Lists as well. Once
-- that happens we can change the Show and Read instances as well to use "1 >:
-- 2 >: nil" etc. or should we use a separate constructor indicating the "List"
-- type ":>" for better inference?
--
-- | @List a@ is a replacement for @[a]@.
--
-- @since 0.6.0
newtype List a = List { forall a. List a -> SerialT Identity a
toSerial :: SerialT Identity a }
    deriving (Int -> List a -> ShowS
forall a. Show a => Int -> List a -> ShowS
forall a. Show a => [List a] -> ShowS
forall a. Show a => List a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [List a] -> ShowS
$cshowList :: forall a. Show a => [List a] -> ShowS
show :: List a -> String
$cshow :: forall a. Show a => List a -> String
showsPrec :: Int -> List a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> List a -> ShowS
Show, ReadPrec [List a]
ReadPrec (List a)
ReadS [List a]
forall a. Read a => ReadPrec [List a]
forall a. Read a => ReadPrec (List a)
forall a. Read a => Int -> ReadS (List a)
forall a. Read a => ReadS [List a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [List a]
$creadListPrec :: forall a. Read a => ReadPrec [List a]
readPrec :: ReadPrec (List a)
$creadPrec :: forall a. Read a => ReadPrec (List a)
readList :: ReadS [List a]
$creadList :: forall a. Read a => ReadS [List a]
readsPrec :: Int -> ReadS (List a)
$creadsPrec :: forall a. Read a => Int -> ReadS (List a)
Read, List a -> List a -> Bool
forall a. Eq a => List a -> List a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: List a -> List a -> Bool
$c/= :: forall a. Eq a => List a -> List a -> Bool
== :: List a -> List a -> Bool
$c== :: forall a. Eq a => List a -> List a -> Bool
Eq, List a -> List a -> Bool
List a -> List a -> Ordering
List a -> List a -> List a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (List a)
forall a. Ord a => List a -> List a -> Bool
forall a. Ord a => List a -> List a -> Ordering
forall a. Ord a => List a -> List a -> List a
min :: List a -> List a -> List a
$cmin :: forall a. Ord a => List a -> List a -> List a
max :: List a -> List a -> List a
$cmax :: forall a. Ord a => List a -> List a -> List a
>= :: List a -> List a -> Bool
$c>= :: forall a. Ord a => List a -> List a -> Bool
> :: List a -> List a -> Bool
$c> :: forall a. Ord a => List a -> List a -> Bool
<= :: List a -> List a -> Bool
$c<= :: forall a. Ord a => List a -> List a -> Bool
< :: List a -> List a -> Bool
$c< :: forall a. Ord a => List a -> List a -> Bool
compare :: List a -> List a -> Ordering
$ccompare :: forall a. Ord a => List a -> List a -> Ordering
Ord, List a -> ()
forall a. NFData a => List a -> ()
forall a. (a -> ()) -> NFData a
rnf :: List a -> ()
$crnf :: forall a. NFData a => List a -> ()
NFData
#if MIN_VERSION_deepseq(1,4,3)
    , forall a. (a -> ()) -> List a -> ()
forall (f :: * -> *).
(forall a. (a -> ()) -> f a -> ()) -> NFData1 f
liftRnf :: forall a. (a -> ()) -> List a -> ()
$cliftRnf :: forall a. (a -> ()) -> List a -> ()
NFData1
#endif
             , NonEmpty (List a) -> List a
List a -> List a -> List a
forall b. Integral b => b -> List a -> List a
forall a. NonEmpty (List a) -> List a
forall a. List a -> List a -> List a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall a b. Integral b => b -> List a -> List a
stimes :: forall b. Integral b => b -> List a -> List a
$cstimes :: forall a b. Integral b => b -> List a -> List a
sconcat :: NonEmpty (List a) -> List a
$csconcat :: forall a. NonEmpty (List a) -> List a
<> :: List a -> List a -> List a
$c<> :: forall a. List a -> List a -> List a
Semigroup, List a
[List a] -> List a
List a -> List a -> List a
forall a. Semigroup (List a)
forall a. List a
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall a. [List a] -> List a
forall a. List a -> List a -> List a
mconcat :: [List a] -> List a
$cmconcat :: forall a. [List a] -> List a
mappend :: List a -> List a -> List a
$cmappend :: forall a. List a -> List a -> List a
mempty :: List a
$cmempty :: forall a. List a
Monoid, forall a b. a -> List b -> List a
forall a b. (a -> b) -> List a -> List b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> List b -> List a
$c<$ :: forall a b. a -> List b -> List a
fmap :: forall a b. (a -> b) -> List a -> List b
$cfmap :: forall a b. (a -> b) -> List a -> List b
Functor, forall a. Eq a => a -> List a -> Bool
forall a. Num a => List a -> a
forall a. Ord a => List a -> a
forall m. Monoid m => List m -> m
forall a. List a -> Bool
forall a. List a -> Int
forall a. List a -> [a]
forall a. (a -> a -> a) -> List a -> a
forall m a. Monoid m => (a -> m) -> List a -> m
forall b a. (b -> a -> b) -> b -> List a -> b
forall a b. (a -> b -> b) -> b -> List a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => List a -> a
$cproduct :: forall a. Num a => List a -> a
sum :: forall a. Num a => List a -> a
$csum :: forall a. Num a => List a -> a
minimum :: forall a. Ord a => List a -> a
$cminimum :: forall a. Ord a => List a -> a
maximum :: forall a. Ord a => List a -> a
$cmaximum :: forall a. Ord a => List a -> a
elem :: forall a. Eq a => a -> List a -> Bool
$celem :: forall a. Eq a => a -> List a -> Bool
length :: forall a. List a -> Int
$clength :: forall a. List a -> Int
null :: forall a. List a -> Bool
$cnull :: forall a. List a -> Bool
toList :: forall a. List a -> [a]
$ctoList :: forall a. List a -> [a]
foldl1 :: forall a. (a -> a -> a) -> List a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> List a -> a
foldr1 :: forall a. (a -> a -> a) -> List a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> List a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> List a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> List a -> b
foldl :: forall b a. (b -> a -> b) -> b -> List a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> List a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> List a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> List a -> b
foldr :: forall a b. (a -> b -> b) -> b -> List a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> List a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> List a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> List a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> List a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> List a -> m
fold :: forall m. Monoid m => List m -> m
$cfold :: forall m. Monoid m => List m -> m
Foldable
             , Functor List
forall a. a -> List a
forall a b. List a -> List b -> List a
forall a b. List a -> List b -> List b
forall a b. List (a -> b) -> List a -> List b
forall a b c. (a -> b -> c) -> List a -> List b -> List c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. List a -> List b -> List a
$c<* :: forall a b. List a -> List b -> List a
*> :: forall a b. List a -> List b -> List b
$c*> :: forall a b. List a -> List b -> List b
liftA2 :: forall a b c. (a -> b -> c) -> List a -> List b -> List c
$cliftA2 :: forall a b c. (a -> b -> c) -> List a -> List b -> List c
<*> :: forall a b. List (a -> b) -> List a -> List b
$c<*> :: forall a b. List (a -> b) -> List a -> List b
pure :: forall a. a -> List a
$cpure :: forall a. a -> List a
Applicative, Functor List
Foldable List
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => List (m a) -> m (List a)
forall (f :: * -> *) a. Applicative f => List (f a) -> f (List a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> List a -> m (List b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> List a -> f (List b)
sequence :: forall (m :: * -> *) a. Monad m => List (m a) -> m (List a)
$csequence :: forall (m :: * -> *) a. Monad m => List (m a) -> m (List a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> List a -> m (List b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> List a -> m (List b)
sequenceA :: forall (f :: * -> *) a. Applicative f => List (f a) -> f (List a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => List (f a) -> f (List a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> List a -> f (List b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> List a -> f (List b)
Traversable, Applicative List
forall a. a -> List a
forall a b. List a -> List b -> List b
forall a b. List a -> (a -> List b) -> List b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> List a
$creturn :: forall a. a -> List a
>> :: forall a b. List a -> List b -> List b
$c>> :: forall a b. List a -> List b -> List b
>>= :: forall a b. List a -> (a -> List b) -> List b
$c>>= :: forall a b. List a -> (a -> List b) -> List b
Monad)

instance (a ~ Char) => IsString (List a) where
    {-# INLINE fromString #-}
    fromString :: String -> List a
fromString = forall a. SerialT Identity a -> List a
List forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall l. IsList l => [Item l] -> l
fromList

-- GHC versions 8.0 and below cannot derive IsList
instance IsList (List a) where
    type (Item (List a)) = a
    {-# INLINE fromList #-}
    fromList :: [Item (List a)] -> List a
fromList = forall a. SerialT Identity a -> List a
List forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall l. IsList l => [Item l] -> l
fromList
    {-# INLINE toList #-}
    toList :: List a -> [Item (List a)]
toList = forall l. IsList l => l -> [Item l]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. List a -> SerialT Identity a
toSerial

------------------------------------------------------------------------------
-- Patterns
------------------------------------------------------------------------------

-- Note: When using the OverloadedLists extension we should be able to pattern
-- match using the regular list contructors. OverloadedLists uses 'toList' to
-- perform the pattern match, it should not be too bad as it works lazily in
-- the Identity monad. We need these patterns only when not using that
-- extension.
--
-- | An empty list constructor and pattern that matches an empty 'List'.
-- Corresponds to '[]' for Haskell lists.
--
-- @since 0.6.0
pattern Nil :: List a
pattern $bNil :: forall a. List a
$mNil :: forall {r} {a}. List a -> ((# #) -> r) -> ((# #) -> r) -> r
Nil <- (runIdentity . K.null . getSerialT . toSerial -> True) where
    Nil = forall a. SerialT Identity a -> List a
List forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Stream m a -> SerialT m a
SerialT forall (m :: * -> *) a. Stream m a
K.nil

infixr 5 `Cons`

-- | A list constructor and pattern that deconstructs a 'List' into its head
-- and tail. Corresponds to ':' for Haskell lists.
--
-- @since 0.6.0
pattern Cons :: a -> List a -> List a
pattern $bCons :: forall a. a -> List a -> List a
$mCons :: forall {r} {a}. List a -> (a -> List a -> r) -> ((# #) -> r) -> r
Cons x xs <-
    (fmap (second (List . SerialT))
        . runIdentity . K.uncons . getSerialT . toSerial
            -> Just (x, xs)
    )

    where

    Cons a
x List a
xs = forall a. SerialT Identity a -> List a
List forall a b. (a -> b) -> a -> b
$ forall a (m :: * -> *). a -> SerialT m a -> SerialT m a
Serial.cons a
x (forall a. List a -> SerialT Identity a
toSerial List a
xs)

#if __GLASGOW_HASKELL__ >= 802
{-# COMPLETE Nil, Cons #-}
#endif

------------------------------------------------------------------------------
-- ZipList
------------------------------------------------------------------------------

-- | Just like 'List' except that it has a zipping 'Applicative' instance
-- and no 'Monad' instance.
--
-- @since 0.6.0
newtype ZipList a = ZipList { forall a. ZipList a -> ZipSerialM Identity a
toZipSerial :: ZipSerialM Identity a }
    deriving (Int -> ZipList a -> ShowS
forall a. Show a => Int -> ZipList a -> ShowS
forall a. Show a => [ZipList a] -> ShowS
forall a. Show a => ZipList a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ZipList a] -> ShowS
$cshowList :: forall a. Show a => [ZipList a] -> ShowS
show :: ZipList a -> String
$cshow :: forall a. Show a => ZipList a -> String
showsPrec :: Int -> ZipList a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ZipList a -> ShowS
Show, ReadPrec [ZipList a]
ReadPrec (ZipList a)
ReadS [ZipList a]
forall a. Read a => ReadPrec [ZipList a]
forall a. Read a => ReadPrec (ZipList a)
forall a. Read a => Int -> ReadS (ZipList a)
forall a. Read a => ReadS [ZipList a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ZipList a]
$creadListPrec :: forall a. Read a => ReadPrec [ZipList a]
readPrec :: ReadPrec (ZipList a)
$creadPrec :: forall a. Read a => ReadPrec (ZipList a)
readList :: ReadS [ZipList a]
$creadList :: forall a. Read a => ReadS [ZipList a]
readsPrec :: Int -> ReadS (ZipList a)
$creadsPrec :: forall a. Read a => Int -> ReadS (ZipList a)
Read, ZipList a -> ZipList a -> Bool
forall a. Eq a => ZipList a -> ZipList a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ZipList a -> ZipList a -> Bool
$c/= :: forall a. Eq a => ZipList a -> ZipList a -> Bool
== :: ZipList a -> ZipList a -> Bool
$c== :: forall a. Eq a => ZipList a -> ZipList a -> Bool
Eq, ZipList a -> ZipList a -> Bool
ZipList a -> ZipList a -> Ordering
ZipList a -> ZipList a -> ZipList a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (ZipList a)
forall a. Ord a => ZipList a -> ZipList a -> Bool
forall a. Ord a => ZipList a -> ZipList a -> Ordering
forall a. Ord a => ZipList a -> ZipList a -> ZipList a
min :: ZipList a -> ZipList a -> ZipList a
$cmin :: forall a. Ord a => ZipList a -> ZipList a -> ZipList a
max :: ZipList a -> ZipList a -> ZipList a
$cmax :: forall a. Ord a => ZipList a -> ZipList a -> ZipList a
>= :: ZipList a -> ZipList a -> Bool
$c>= :: forall a. Ord a => ZipList a -> ZipList a -> Bool
> :: ZipList a -> ZipList a -> Bool
$c> :: forall a. Ord a => ZipList a -> ZipList a -> Bool
<= :: ZipList a -> ZipList a -> Bool
$c<= :: forall a. Ord a => ZipList a -> ZipList a -> Bool
< :: ZipList a -> ZipList a -> Bool
$c< :: forall a. Ord a => ZipList a -> ZipList a -> Bool
compare :: ZipList a -> ZipList a -> Ordering
$ccompare :: forall a. Ord a => ZipList a -> ZipList a -> Ordering
Ord, ZipList a -> ()
forall a. NFData a => ZipList a -> ()
forall a. (a -> ()) -> NFData a
rnf :: ZipList a -> ()
$crnf :: forall a. NFData a => ZipList a -> ()
NFData
#if MIN_VERSION_deepseq(1,4,3)
    , forall a. (a -> ()) -> ZipList a -> ()
forall (f :: * -> *).
(forall a. (a -> ()) -> f a -> ()) -> NFData1 f
liftRnf :: forall a. (a -> ()) -> ZipList a -> ()
$cliftRnf :: forall a. (a -> ()) -> ZipList a -> ()
NFData1
#endif
             , NonEmpty (ZipList a) -> ZipList a
ZipList a -> ZipList a -> ZipList a
forall b. Integral b => b -> ZipList a -> ZipList a
forall a. NonEmpty (ZipList a) -> ZipList a
forall a. ZipList a -> ZipList a -> ZipList a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall a b. Integral b => b -> ZipList a -> ZipList a
stimes :: forall b. Integral b => b -> ZipList a -> ZipList a
$cstimes :: forall a b. Integral b => b -> ZipList a -> ZipList a
sconcat :: NonEmpty (ZipList a) -> ZipList a
$csconcat :: forall a. NonEmpty (ZipList a) -> ZipList a
<> :: ZipList a -> ZipList a -> ZipList a
$c<> :: forall a. ZipList a -> ZipList a -> ZipList a
Semigroup, ZipList a
[ZipList a] -> ZipList a
ZipList a -> ZipList a -> ZipList a
forall a. Semigroup (ZipList a)
forall a. ZipList a
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall a. [ZipList a] -> ZipList a
forall a. ZipList a -> ZipList a -> ZipList a
mconcat :: [ZipList a] -> ZipList a
$cmconcat :: forall a. [ZipList a] -> ZipList a
mappend :: ZipList a -> ZipList a -> ZipList a
$cmappend :: forall a. ZipList a -> ZipList a -> ZipList a
mempty :: ZipList a
$cmempty :: forall a. ZipList a
Monoid, forall a b. a -> ZipList b -> ZipList a
forall a b. (a -> b) -> ZipList a -> ZipList b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> ZipList b -> ZipList a
$c<$ :: forall a b. a -> ZipList b -> ZipList a
fmap :: forall a b. (a -> b) -> ZipList a -> ZipList b
$cfmap :: forall a b. (a -> b) -> ZipList a -> ZipList b
Functor, forall a. Eq a => a -> ZipList a -> Bool
forall a. Num a => ZipList a -> a
forall a. Ord a => ZipList a -> a
forall m. Monoid m => ZipList m -> m
forall a. ZipList a -> Bool
forall a. ZipList a -> Int
forall a. ZipList a -> [a]
forall a. (a -> a -> a) -> ZipList a -> a
forall m a. Monoid m => (a -> m) -> ZipList a -> m
forall b a. (b -> a -> b) -> b -> ZipList a -> b
forall a b. (a -> b -> b) -> b -> ZipList a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => ZipList a -> a
$cproduct :: forall a. Num a => ZipList a -> a
sum :: forall a. Num a => ZipList a -> a
$csum :: forall a. Num a => ZipList a -> a
minimum :: forall a. Ord a => ZipList a -> a
$cminimum :: forall a. Ord a => ZipList a -> a
maximum :: forall a. Ord a => ZipList a -> a
$cmaximum :: forall a. Ord a => ZipList a -> a
elem :: forall a. Eq a => a -> ZipList a -> Bool
$celem :: forall a. Eq a => a -> ZipList a -> Bool
length :: forall a. ZipList a -> Int
$clength :: forall a. ZipList a -> Int
null :: forall a. ZipList a -> Bool
$cnull :: forall a. ZipList a -> Bool
toList :: forall a. ZipList a -> [a]
$ctoList :: forall a. ZipList a -> [a]
foldl1 :: forall a. (a -> a -> a) -> ZipList a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> ZipList a -> a
foldr1 :: forall a. (a -> a -> a) -> ZipList a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> ZipList a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> ZipList a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> ZipList a -> b
foldl :: forall b a. (b -> a -> b) -> b -> ZipList a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> ZipList a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> ZipList a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> ZipList a -> b
foldr :: forall a b. (a -> b -> b) -> b -> ZipList a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> ZipList a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> ZipList a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> ZipList a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> ZipList a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> ZipList a -> m
fold :: forall m. Monoid m => ZipList m -> m
$cfold :: forall m. Monoid m => ZipList m -> m
Foldable
             , Functor ZipList
forall a. a -> ZipList a
forall a b. ZipList a -> ZipList b -> ZipList a
forall a b. ZipList a -> ZipList b -> ZipList b
forall a b. ZipList (a -> b) -> ZipList a -> ZipList b
forall a b c. (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. ZipList a -> ZipList b -> ZipList a
$c<* :: forall a b. ZipList a -> ZipList b -> ZipList a
*> :: forall a b. ZipList a -> ZipList b -> ZipList b
$c*> :: forall a b. ZipList a -> ZipList b -> ZipList b
liftA2 :: forall a b c. (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c
$cliftA2 :: forall a b c. (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c
<*> :: forall a b. ZipList (a -> b) -> ZipList a -> ZipList b
$c<*> :: forall a b. ZipList (a -> b) -> ZipList a -> ZipList b
pure :: forall a. a -> ZipList a
$cpure :: forall a. a -> ZipList a
Applicative, Functor ZipList
Foldable ZipList
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => ZipList (m a) -> m (ZipList a)
forall (f :: * -> *) a.
Applicative f =>
ZipList (f a) -> f (ZipList a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ZipList a -> m (ZipList b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ZipList a -> f (ZipList b)
sequence :: forall (m :: * -> *) a. Monad m => ZipList (m a) -> m (ZipList a)
$csequence :: forall (m :: * -> *) a. Monad m => ZipList (m a) -> m (ZipList a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ZipList a -> m (ZipList b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ZipList a -> m (ZipList b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
ZipList (f a) -> f (ZipList a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
ZipList (f a) -> f (ZipList a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ZipList a -> f (ZipList b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ZipList a -> f (ZipList b)
Traversable)

instance (a ~ Char) => IsString (ZipList a) where
    {-# INLINE fromString #-}
    fromString :: String -> ZipList a
fromString = forall a. ZipSerialM Identity a -> ZipList a
ZipList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall l. IsList l => [Item l] -> l
fromList

-- GHC versions 8.0 and below cannot derive IsList
instance IsList (ZipList a) where
    type (Item (ZipList a)) = a
    {-# INLINE fromList #-}
    fromList :: [Item (ZipList a)] -> ZipList a
fromList = forall a. ZipSerialM Identity a -> ZipList a
ZipList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall l. IsList l => [Item l] -> l
fromList
    {-# INLINE toList #-}
    toList :: ZipList a -> [Item (ZipList a)]
toList = forall l. IsList l => l -> [Item l]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ZipList a -> ZipSerialM Identity a
toZipSerial

-- | Convert a 'ZipList' to a regular 'List'
--
-- @since 0.6.0
fromZipList :: ZipList a -> List a
fromZipList :: forall a. ZipList a -> List a
fromZipList (ZipList ZipSerialM Identity a
zs) = forall a. SerialT Identity a -> List a
List forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Stream m a -> SerialT m a
SerialT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ZipSerialM m a -> Stream m a
getZipSerialM ZipSerialM Identity a
zs

-- | Convert a regular 'List' to a 'ZipList'
--
-- @since 0.6.0
toZipList :: List a -> ZipList a
toZipList :: forall a. List a -> ZipList a
toZipList = forall a. ZipSerialM Identity a -> ZipList a
ZipList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Stream m a -> ZipSerialM m a
ZipSerialM forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. SerialT m a -> Stream m a
getSerialT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. List a -> SerialT Identity a
toSerial