| Copyright | (C) 2011-2015 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Data.Semigroup.Foldable
Description
Synopsis
- class Foldable t => Foldable1 t where
 - intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m
 - intercalateMap1 :: (Foldable1 t, Semigroup m) => m -> (a -> m) -> t a -> m
 - traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f ()
 - for1_ :: (Foldable1 t, Apply f) => t a -> (a -> f b) -> f ()
 - sequenceA1_ :: (Foldable1 t, Apply f) => t (f a) -> f ()
 - foldMapDefault1 :: (Foldable1 t, Monoid m) => (a -> m) -> t a -> m
 - asum1 :: (Foldable1 t, Alt m) => t (m a) -> m a
 - foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a
 - foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a
 
Documentation
class Foldable t => Foldable1 t where Source #
Minimal complete definition
Nothing
Methods
fold1 :: Semigroup m => t m -> m Source #
foldMap1 :: Semigroup m => (a -> m) -> t a -> m Source #
toNonEmpty :: t a -> NonEmpty a Source #
Instances
intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m Source #
Insert an m between each pair of t m.  Equivalent to
 intercalateMap1 with id as the second argument.
>>>intercalate1 ", " $ "hello" :| ["how", "are", "you"]"hello, how, are, you"
>>>intercalate1 ", " $ "hello" :| []"hello"
>>>intercalate1 mempty $ "I" :| ["Am", "Fine", "You?"]"IAmFineYou?"
intercalateMap1 :: (Foldable1 t, Semigroup m) => m -> (a -> m) -> t a -> m Source #
Insert m between each pair of m derived from a.
>>>intercalateMap1 " " show $ True :| [False, True]"True False True"
>>>intercalateMap1 " " show $ True :| []"True"
traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () Source #
sequenceA1_ :: (Foldable1 t, Apply f) => t (f a) -> f () Source #
foldMapDefault1 :: (Foldable1 t, Monoid m) => (a -> m) -> t a -> m Source #
Usable default for foldMap, but only if you define foldMap1 yourself