{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveDataTypeable #-} module GHC.Internal.Functor.ZipList (ZipList(..)) where import GHC.Internal.Base import GHC.Internal.Generics import GHC.Internal.List (repeat, zipWith) import GHC.Internal.Read (Read) import GHC.Internal.Show (Show) import GHC.Internal.Data.Foldable (Foldable) import GHC.Internal.Data.Traversable (Traversable(..)) import GHC.Internal.Data.Data (Data) newtype ZipList a = ZipList { forall a. ZipList a -> [a] getZipList :: [a] } deriving ( Int -> ZipList a -> ShowS [ZipList a] -> ShowS ZipList a -> String (Int -> ZipList a -> ShowS) -> (ZipList a -> String) -> ([ZipList a] -> ShowS) -> Show (ZipList a) 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 $cshowsPrec :: forall a. Show a => Int -> ZipList a -> ShowS showsPrec :: Int -> ZipList a -> ShowS $cshow :: forall a. Show a => ZipList a -> String show :: ZipList a -> String $cshowList :: forall a. Show a => [ZipList a] -> ShowS showList :: [ZipList a] -> ShowS Show , ZipList a -> ZipList a -> Bool (ZipList a -> ZipList a -> Bool) -> (ZipList a -> ZipList a -> Bool) -> Eq (ZipList a) forall a. Eq a => ZipList a -> ZipList a -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $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 /= :: ZipList a -> ZipList a -> Bool Eq , Eq (ZipList a) Eq (ZipList a) => (ZipList a -> ZipList a -> Ordering) -> (ZipList a -> ZipList a -> Bool) -> (ZipList a -> ZipList a -> Bool) -> (ZipList a -> ZipList a -> Bool) -> (ZipList a -> ZipList a -> Bool) -> (ZipList a -> ZipList a -> ZipList a) -> (ZipList a -> ZipList a -> ZipList a) -> Ord (ZipList a) 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 $ccompare :: forall a. Ord a => ZipList a -> ZipList a -> Ordering compare :: ZipList a -> ZipList a -> Ordering $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 >= :: ZipList a -> ZipList a -> Bool $cmax :: forall a. Ord a => ZipList a -> ZipList a -> ZipList a max :: ZipList a -> ZipList a -> ZipList a $cmin :: forall a. Ord a => ZipList a -> ZipList a -> ZipList a min :: ZipList a -> ZipList a -> ZipList a Ord , ReadPrec [ZipList a] ReadPrec (ZipList a) Int -> ReadS (ZipList a) ReadS [ZipList a] (Int -> ReadS (ZipList a)) -> ReadS [ZipList a] -> ReadPrec (ZipList a) -> ReadPrec [ZipList a] -> Read (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 $creadsPrec :: forall a. Read a => Int -> ReadS (ZipList a) readsPrec :: Int -> ReadS (ZipList a) $creadList :: forall a. Read a => ReadS [ZipList a] readList :: ReadS [ZipList a] $creadPrec :: forall a. Read a => ReadPrec (ZipList a) readPrec :: ReadPrec (ZipList a) $creadListPrec :: forall a. Read a => ReadPrec [ZipList a] readListPrec :: ReadPrec [ZipList a] Read , (forall a b. (a -> b) -> ZipList a -> ZipList b) -> (forall a b. a -> ZipList b -> ZipList a) -> Functor ZipList 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 $cfmap :: forall a b. (a -> b) -> ZipList a -> ZipList b fmap :: forall a b. (a -> b) -> ZipList a -> ZipList b $c<$ :: forall a b. a -> ZipList b -> ZipList a <$ :: forall a b. a -> ZipList b -> ZipList a Functor , (forall m. Monoid m => ZipList m -> m) -> (forall m a. Monoid m => (a -> m) -> ZipList a -> m) -> (forall m a. Monoid m => (a -> m) -> ZipList a -> m) -> (forall a b. (a -> b -> b) -> b -> ZipList a -> b) -> (forall a b. (a -> b -> b) -> b -> ZipList a -> b) -> (forall b a. (b -> a -> b) -> b -> ZipList a -> b) -> (forall b a. (b -> a -> b) -> b -> ZipList a -> b) -> (forall a. (a -> a -> a) -> ZipList a -> a) -> (forall a. (a -> a -> a) -> ZipList a -> a) -> (forall a. ZipList a -> [a]) -> (forall a. ZipList a -> Bool) -> (forall a. ZipList a -> Int) -> (forall a. Eq a => a -> ZipList a -> Bool) -> (forall a. Ord a => ZipList a -> a) -> (forall a. Ord a => ZipList a -> a) -> (forall a. Num a => ZipList a -> a) -> (forall a. Num a => ZipList a -> a) -> Foldable ZipList 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 $cfold :: forall m. Monoid m => ZipList m -> m fold :: forall m. Monoid m => ZipList m -> 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 foldMap' :: forall m a. Monoid m => (a -> m) -> ZipList a -> m $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 foldr' :: forall a b. (a -> b -> 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 foldl' :: forall b a. (b -> a -> b) -> b -> ZipList a -> b $cfoldr1 :: forall a. (a -> a -> a) -> ZipList a -> a foldr1 :: forall a. (a -> a -> a) -> ZipList a -> a $cfoldl1 :: forall a. (a -> a -> a) -> ZipList a -> a foldl1 :: forall a. (a -> a -> a) -> ZipList a -> a $ctoList :: forall a. ZipList a -> [a] toList :: forall a. ZipList a -> [a] $cnull :: forall a. ZipList a -> Bool null :: forall a. ZipList a -> Bool $clength :: forall a. ZipList a -> Int length :: forall a. ZipList a -> Int $celem :: forall a. Eq a => a -> ZipList a -> Bool elem :: forall a. Eq a => a -> ZipList a -> Bool $cmaximum :: forall a. Ord a => ZipList a -> a maximum :: forall a. Ord a => ZipList a -> a $cminimum :: forall a. Ord a => ZipList a -> a minimum :: forall a. Ord a => ZipList a -> a $csum :: forall a. Num a => ZipList a -> a sum :: forall a. Num a => ZipList a -> a $cproduct :: forall a. Num a => ZipList a -> a product :: forall a. Num a => ZipList a -> a Foldable , (forall x. ZipList a -> Rep (ZipList a) x) -> (forall x. Rep (ZipList a) x -> ZipList a) -> Generic (ZipList a) forall x. Rep (ZipList a) x -> ZipList a forall x. ZipList a -> Rep (ZipList a) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall a x. Rep (ZipList a) x -> ZipList a forall a x. ZipList a -> Rep (ZipList a) x $cfrom :: forall a x. ZipList a -> Rep (ZipList a) x from :: forall x. ZipList a -> Rep (ZipList a) x $cto :: forall a x. Rep (ZipList a) x -> ZipList a to :: forall x. Rep (ZipList a) x -> ZipList a Generic , (forall a. ZipList a -> Rep1 ZipList a) -> (forall a. Rep1 ZipList a -> ZipList a) -> Generic1 ZipList forall a. Rep1 ZipList a -> ZipList a forall a. ZipList a -> Rep1 ZipList a forall k (f :: k -> *). (forall (a :: k). f a -> Rep1 f a) -> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f $cfrom1 :: forall a. ZipList a -> Rep1 ZipList a from1 :: forall a. ZipList a -> Rep1 ZipList a $cto1 :: forall a. Rep1 ZipList a -> ZipList a to1 :: forall a. Rep1 ZipList a -> ZipList a Generic1 ) instance Traversable ZipList where traverse :: forall (f :: * -> *) a b. Applicative f => (a -> f b) -> ZipList a -> f (ZipList b) traverse a -> f b f (ZipList [a] x) = [b] -> ZipList b forall a. [a] -> ZipList a ZipList ([b] -> ZipList b) -> f [b] -> f (ZipList b) forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b `fmap` (a -> f b) -> [a] -> f [b] forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) forall (f :: * -> *) a b. Applicative f => (a -> f b) -> [a] -> f [b] traverse a -> f b f [a] x instance Applicative ZipList where pure :: forall a. a -> ZipList a pure a x = [a] -> ZipList a forall a. [a] -> ZipList a ZipList (a -> [a] forall a. a -> [a] repeat a x) liftA2 :: forall a b c. (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c liftA2 a -> b -> c f (ZipList [a] xs) (ZipList [b] ys) = [c] -> ZipList c forall a. [a] -> ZipList a ZipList ((a -> b -> c) -> [a] -> [b] -> [c] forall a b c. (a -> b -> c) -> [a] -> [b] -> [c] zipWith a -> b -> c f [a] xs [b] ys) instance Alternative ZipList where empty :: forall a. ZipList a empty = [a] -> ZipList a forall a. [a] -> ZipList a ZipList [] ZipList [a] xs0 <|> :: forall a. ZipList a -> ZipList a -> ZipList a <|> ZipList [a] ys0 = [a] -> ZipList a forall a. [a] -> ZipList a ZipList ([a] -> ZipList a) -> [a] -> ZipList a forall a b. (a -> b) -> a -> b $ [a] -> [a] -> [a] forall {a}. [a] -> [a] -> [a] go [a] xs0 [a] ys0 where go :: [a] -> [a] -> [a] go (a x:[a] xs) (a _:[a] ys) = a x a -> [a] -> [a] forall a. a -> [a] -> [a] : [a] -> [a] -> [a] go [a] xs [a] ys go [] [a] ys = [a] ys go [a] xs [a] _ = [a] xs deriving instance Data a => Data (ZipList a)
RetroSearch is an open source project built by @garambo | Open a GitHub Issue
Search and Browse the WWW like it's 1997 | Search results from DuckDuckGo
HTML:
3.2
| Encoding:
UTF-8
| Version:
0.7.4