{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Safe #-}
#elif __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
-- | Indexed Foldables.moduleData.Foldable.WithIndex(-- * Indexed FoldablesFoldableWithIndex (..),-- ** Indexed Foldable Combinatorsiany ,iall ,inone ,none ,itraverse_ ,ifor_ ,imapM_ ,iforM_ ,iconcatMap ,ifind ,ifoldrM ,ifoldlM ,itoList ,)whereimportPrelude(Bool,Maybe(..),Monad(..),flip,not,(.),curry)importControl.Applicative(Applicative(..))importControl.Monad(liftM,void)importData.Foldable(Foldable,any)importData.Monoid(All(..),Any(..))importGhcExts (build)importWithIndex -- | Return whether or not any element in a container satisfies a predicate, with access to the index @i@.---- When you don't need access to the index then 'any' is more flexible in what it accepts.---- @-- 'any' ≡ 'iany' '.' 'const'-- @iany ::FoldableWithIndex i f =>(i ->a ->Bool)->f a ->Booliany :: (i -> a -> Bool) -> f a -> Bool
iany i -> a -> Bool
f =Any -> Bool
getAny(Any -> Bool) -> (f a -> Any) -> f a -> Bool
forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. (i -> a -> Any) -> f a -> Any
forall i (f :: * -> *) m a.
(FoldableWithIndex i f, Monoid m) =>
(i -> a -> m) -> f a -> m
ifoldMap (Bool -> Any
Any(Bool -> Any) -> (i -> a -> Bool) -> i -> a -> Any
forall b c i a.
Coercible b c =>
(b -> c) -> (i -> a -> b) -> i -> a -> c
#.. i -> a -> Bool
f ){-# INLINEiany #-}-- | Return whether or not all elements in a container satisfy a predicate, with access to the index @i@.---- When you don't need access to the index then 'all' is more flexible in what it accepts.---- @-- 'all' ≡ 'iall' '.' 'const'-- @iall ::FoldableWithIndex i f =>(i ->a ->Bool)->f a ->Booliall :: (i -> a -> Bool) -> f a -> Bool
iall i -> a -> Bool
f =All -> Bool
getAll(All -> Bool) -> (f a -> All) -> f a -> Bool
forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. (i -> a -> All) -> f a -> All
forall i (f :: * -> *) m a.
(FoldableWithIndex i f, Monoid m) =>
(i -> a -> m) -> f a -> m
ifoldMap (Bool -> All
All(Bool -> All) -> (i -> a -> Bool) -> i -> a -> All
forall b c i a.
Coercible b c =>
(b -> c) -> (i -> a -> b) -> i -> a -> c
#.. i -> a -> Bool
f ){-# INLINEiall #-}-- | Return whether or not none of the elements in a container satisfy a predicate, with access to the index @i@.---- When you don't need access to the index then 'none' is more flexible in what it accepts.---- @-- 'none' ≡ 'inone' '.' 'const'-- 'inone' f ≡ 'not' '.' 'iany' f-- @inone ::FoldableWithIndex i f =>(i ->a ->Bool)->f a ->Boolinone :: (i -> a -> Bool) -> f a -> Bool
inone i -> a -> Bool
f =Bool -> Bool
not(Bool -> Bool) -> (f a -> Bool) -> f a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(i -> a -> Bool) -> f a -> Bool
forall i (f :: * -> *) a.
FoldableWithIndex i f =>
(i -> a -> Bool) -> f a -> Bool
iany i -> a -> Bool
f {-# INLINEinone #-}-- | Determines whether no elements of the structure satisfy the predicate.---- @-- 'none' f ≡ 'not' '.' 'any' f-- @none ::Foldablef =>(a ->Bool)->f a ->Boolnone :: (a -> Bool) -> f a -> Bool
none a -> Bool
f =Bool -> Bool
not(Bool -> Bool) -> (f a -> Bool) -> f a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(a -> Bool) -> f a -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
anya -> Bool
f {-# INLINEnone #-}-- | Traverse elements with access to the index @i@, discarding the results.---- When you don't need access to the index then 'traverse_' is more flexible in what it accepts.---- @-- 'traverse_' l = 'itraverse' '.' 'const'-- @itraverse_ ::(FoldableWithIndex i t ,Applicativef )=>(i ->a ->f b )->t a ->f ()itraverse_ :: (i -> a -> f b) -> t a -> f ()
itraverse_ i -> a -> f b
f =f b -> f ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void(f b -> f ()) -> (t a -> f b) -> t a -> f ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Traversed b f -> f b
forall k (a :: k) (f :: k -> *). Traversed a f -> f a
getTraversed (Traversed b f -> f b) -> (t a -> Traversed b f) -> t a -> f b
forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. (i -> a -> Traversed b f) -> t a -> Traversed b f
forall i (f :: * -> *) m a.
(FoldableWithIndex i f, Monoid m) =>
(i -> a -> m) -> f a -> m
ifoldMap (f b -> Traversed b f
forall k (a :: k) (f :: k -> *). f a -> Traversed a f
Traversed (f b -> Traversed b f)
-> (i -> a -> f b) -> i -> a -> Traversed b f
forall b c i a.
Coercible b c =>
(b -> c) -> (i -> a -> b) -> i -> a -> c
#.. i -> a -> f b
f ){-# INLINEitraverse_ #-}-- | Traverse elements with access to the index @i@, discarding the results (with the arguments flipped).---- @-- 'ifor_' ≡ 'flip' 'itraverse_'-- @---- When you don't need access to the index then 'for_' is more flexible in what it accepts.---- @-- 'for_' a ≡ 'ifor_' a '.' 'const'-- @ifor_ ::(FoldableWithIndex i t ,Applicativef )=>t a ->(i ->a ->f b )->f ()ifor_ :: t a -> (i -> a -> f b) -> f ()
ifor_ =((i -> a -> f b) -> t a -> f ()) -> t a -> (i -> a -> f b) -> f ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip(i -> a -> f b) -> t a -> f ()
forall i (t :: * -> *) (f :: * -> *) a b.
(FoldableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f ()
itraverse_ {-# INLINEifor_ #-}-- | Run monadic actions for each target of an 'IndexedFold' or 'Control.Lens.IndexedTraversal.IndexedTraversal' with access to the index,-- discarding the results.---- When you don't need access to the index then 'Control.Lens.Fold.mapMOf_' is more flexible in what it accepts.---- @-- 'mapM_' ≡ 'imapM' '.' 'const'-- @imapM_ ::(FoldableWithIndex i t ,Monadm )=>(i ->a ->m b )->t a ->m ()imapM_ :: (i -> a -> m b) -> t a -> m ()
imapM_ i -> a -> m b
f =(b -> ()) -> m b -> m ()
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftMb -> ()
forall a. a -> ()
skip (m b -> m ()) -> (t a -> m b) -> t a -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Sequenced b m -> m b
forall k (a :: k) (m :: k -> *). Sequenced a m -> m a
getSequenced (Sequenced b m -> m b) -> (t a -> Sequenced b m) -> t a -> m b
forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. (i -> a -> Sequenced b m) -> t a -> Sequenced b m
forall i (f :: * -> *) m a.
(FoldableWithIndex i f, Monoid m) =>
(i -> a -> m) -> f a -> m
ifoldMap (m b -> Sequenced b m
forall k (a :: k) (m :: k -> *). m a -> Sequenced a m
Sequenced (m b -> Sequenced b m)
-> (i -> a -> m b) -> i -> a -> Sequenced b m
forall b c i a.
Coercible b c =>
(b -> c) -> (i -> a -> b) -> i -> a -> c
#.. i -> a -> m b
f ){-# INLINEimapM_ #-}-- | Run monadic actions for each target of an 'IndexedFold' or 'Control.Lens.IndexedTraversal.IndexedTraversal' with access to the index,-- discarding the results (with the arguments flipped).---- @-- 'iforM_' ≡ 'flip' 'imapM_'-- @---- When you don't need access to the index then 'Control.Monad.forM_' is more flexible in what it accepts.---- @-- 'Control.Monad.forM_' a ≡ 'iforM' a '.' 'const'-- @iforM_ ::(FoldableWithIndex i t ,Monadm )=>t a ->(i ->a ->m b )->m ()iforM_ :: t a -> (i -> a -> m b) -> m ()
iforM_ =((i -> a -> m b) -> t a -> m ()) -> t a -> (i -> a -> m b) -> m ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip(i -> a -> m b) -> t a -> m ()
forall i (t :: * -> *) (m :: * -> *) a b.
(FoldableWithIndex i t, Monad m) =>
(i -> a -> m b) -> t a -> m ()
imapM_ {-# INLINEiforM_ #-}-- | Concatenate the results of a function of the elements of an indexed container with access to the index.---- When you don't need access to the index then 'concatMap' is more flexible in what it accepts.---- @-- 'concatMap' ≡ 'iconcatMap' '.' 'const'-- 'iconcatMap' ≡ 'ifoldMap'-- @iconcatMap ::FoldableWithIndex i f =>(i ->a ->[b ])->f a ->[b ]iconcatMap :: (i -> a -> [b]) -> f a -> [b]
iconcatMap =(i -> a -> [b]) -> f a -> [b]
forall i (f :: * -> *) m a.
(FoldableWithIndex i f, Monoid m) =>
(i -> a -> m) -> f a -> m
ifoldMap {-# INLINEiconcatMap #-}-- | Searches a container with a predicate that is also supplied the index, returning the left-most element of the structure-- matching the predicate, or 'Nothing' if there is no such element.---- When you don't need access to the index then 'find' is more flexible in what it accepts.---- @-- 'find' ≡ 'ifind' '.' 'const'-- @ifind ::FoldableWithIndex i f =>(i ->a ->Bool)->f a ->Maybe(i ,a )ifind :: (i -> a -> Bool) -> f a -> Maybe (i, a)
ifind i -> a -> Bool
p =(i -> a -> Maybe (i, a) -> Maybe (i, a))
-> Maybe (i, a) -> f a -> Maybe (i, a)
forall i (f :: * -> *) a b.
FoldableWithIndex i f =>
(i -> a -> b -> b) -> b -> f a -> b
ifoldr (\i
i a
a Maybe (i, a)
y ->ifi -> a -> Bool
p i
i a
a then(i, a) -> Maybe (i, a)
forall a. a -> Maybe a
Just(i
i ,a
a )elseMaybe (i, a)
y )Maybe (i, a)
forall a. Maybe a
Nothing{-# INLINEifind #-}-- | Monadic fold right over the elements of a structure with an index.---- When you don't need access to the index then 'foldrM' is more flexible in what it accepts.---- @-- 'foldrM' ≡ 'ifoldrM' '.' 'const'-- @ifoldrM ::(FoldableWithIndex i f ,Monadm )=>(i ->a ->b ->m b )->b ->f a ->m b ifoldrM :: (i -> a -> b -> m b) -> b -> f a -> m b
ifoldrM i -> a -> b -> m b
f b
z0 f a
xs =(i -> (b -> m b) -> a -> b -> m b) -> (b -> m b) -> f a -> b -> m b
forall i (f :: * -> *) b a.
FoldableWithIndex i f =>
(i -> b -> a -> b) -> b -> f a -> b
ifoldl i -> (b -> m b) -> a -> b -> m b
forall b. i -> (b -> m b) -> a -> b -> m b
f' b -> m b
forall (m :: * -> *) a. Monad m => a -> m a
returnf a
xs b
z0 wheref' :: i -> (b -> m b) -> a -> b -> m b
f' i
i b -> m b
k a
x b
z =i -> a -> b -> m b
f i
i a
x b
z m b -> (b -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=b -> m b
k {-# INLINEifoldrM #-}-- | Monadic fold over the elements of a structure with an index, associating to the left.---- When you don't need access to the index then 'foldlM' is more flexible in what it accepts.---- @-- 'foldlM' ≡ 'ifoldlM' '.' 'const'-- @ifoldlM ::(FoldableWithIndex i f ,Monadm )=>(i ->b ->a ->m b )->b ->f a ->m b ifoldlM :: (i -> b -> a -> m b) -> b -> f a -> m b
ifoldlM i -> b -> a -> m b
f b
z0 f a
xs =(i -> a -> (b -> m b) -> b -> m b) -> (b -> m b) -> f a -> b -> m b
forall i (f :: * -> *) a b.
FoldableWithIndex i f =>
(i -> a -> b -> b) -> b -> f a -> b
ifoldr i -> a -> (b -> m b) -> b -> m b
forall b. i -> a -> (b -> m b) -> b -> m b
f' b -> m b
forall (m :: * -> *) a. Monad m => a -> m a
returnf a
xs b
z0 wheref' :: i -> a -> (b -> m b) -> b -> m b
f' i
i a
x b -> m b
k b
z =i -> b -> a -> m b
f i
i b
z a
x m b -> (b -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=b -> m b
k {-# INLINEifoldlM #-}-- | Extract the key-value pairs from a structure.---- When you don't need access to the indices in the result, then 'toList' is more flexible in what it accepts.---- @-- 'toList' ≡ 'Data.List.map' 'snd' '.' 'itoList'-- @itoList ::FoldableWithIndex i f =>f a ->[(i ,a )]itoList :: f a -> [(i, a)]
itoList f a
xs =(forall b. ((i, a) -> b -> b) -> b -> b) -> [(i, a)]
forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build(\(i, a) -> b -> b
c b
n ->(i -> a -> b -> b) -> b -> f a -> b
forall i (f :: * -> *) a b.
FoldableWithIndex i f =>
(i -> a -> b -> b) -> b -> f a -> b
ifoldr (((i, a) -> b -> b) -> i -> a -> b -> b
forall a b c. ((a, b) -> c) -> a -> b -> c
curry(i, a) -> b -> b
c )b
n f a
xs ){-# INLINEitoList #-}

AltStyle によって変換されたページ (->オリジナル) /