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 | Haskell98 |
- 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
Documentation
class Foldable t => Foldable1 t where Source #
Foldable1 Identity Source # | |
Foldable1 NonEmpty Source # | |
Foldable1 Tree Source # | |
Foldable1 ((,) a) Source # | |
Foldable1 f => Foldable1 (Lift f) Source # | |
Bifoldable1 p => Foldable1 (Join * p) Source # | |
Foldable1 m => Foldable1 (IdentityT * m) Source # | |
Foldable1 f => Foldable1 (Reverse * f) Source # | |
Foldable1 f => Foldable1 (Backwards * f) Source # | |
(Foldable1 f, Foldable1 g) => Foldable1 (Sum * f g) Source # | |
(Foldable1 f, Foldable1 g) => Foldable1 (Product * f g) Source # | |
(Foldable1 f, Foldable1 g) => Foldable1 (Compose * * f g) Source # | |
Foldable1 g => Foldable1 (Joker * * g a) Source # | |
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