| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
RIO.NonEmpty
Contents
Description
NonEmpty list. Import as:
import qualified RIO.NonEmpty as NE
This module does not export any partial functions. For those, see RIO.NonEmpty.Partial
Synopsis
- data NonEmpty a = a :| [a]
- map :: (a -> b) -> NonEmpty a -> NonEmpty b
- intersperse :: a -> NonEmpty a -> NonEmpty a
- scanl :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b
- scanr :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b
- scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
- scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
- transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
- sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
- sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
- length :: NonEmpty a -> Int
- head :: NonEmpty a -> a
- tail :: NonEmpty a -> [a]
- last :: NonEmpty a -> a
- init :: NonEmpty a -> [a]
- (<|) :: a -> NonEmpty a -> NonEmpty a
- cons :: a -> NonEmpty a -> NonEmpty a
- uncons :: NonEmpty a -> (a, Maybe (NonEmpty a))
- unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b
- sort :: Ord a => NonEmpty a -> NonEmpty a
- reverse :: NonEmpty a -> NonEmpty a
- inits :: Foldable f => f a -> NonEmpty [a]
- tails :: Foldable f => f a -> NonEmpty [a]
- iterate :: (a -> a) -> a -> NonEmpty a
- repeat :: a -> NonEmpty a
- cycle :: NonEmpty a -> NonEmpty a
- insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a
- some1 :: Alternative f => f a -> f (NonEmpty a)
- take :: Int -> NonEmpty a -> [a]
- drop :: Int -> NonEmpty a -> [a]
- splitAt :: Int -> NonEmpty a -> ([a], [a])
- takeWhile :: (a -> Bool) -> NonEmpty a -> [a]
- dropWhile :: (a -> Bool) -> NonEmpty a -> [a]
- span :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- break :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- filter :: (a -> Bool) -> NonEmpty a -> [a]
- partition :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- group :: (Foldable f, Eq a) => f a -> [NonEmpty a]
- groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a]
- groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a]
- groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a]
- group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
- groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool
- nub :: Eq a => NonEmpty a -> NonEmpty a
- nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
- zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
- zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
- unzip :: Functor f => f (a, b) -> (f a, f b)
- nonEmpty :: [a] -> Maybe (NonEmpty a)
- toList :: NonEmpty a -> [a]
- xor :: NonEmpty Bool -> Bool
The type of non-empty streams
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
Constructors
| a :| [a] infixr 5 | 
Instances
| Monad NonEmpty | Since: base-4.9.0.0 | 
| Functor NonEmpty | Since: base-4.9.0.0 | 
| Applicative NonEmpty | Since: base-4.9.0.0 | 
| Foldable NonEmpty | Since: base-4.9.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => NonEmpty m -> m # foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m # foldr :: (a -> b -> b) -> b -> NonEmpty a -> b # foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b # foldl :: (b -> a -> b) -> b -> NonEmpty a -> b # foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b # foldr1 :: (a -> a -> a) -> NonEmpty a -> a # foldl1 :: (a -> a -> a) -> NonEmpty a -> a # elem :: Eq a => a -> NonEmpty a -> Bool # maximum :: Ord a => NonEmpty a -> a # minimum :: Ord a => NonEmpty a -> a # | |
| Traversable NonEmpty | Since: base-4.9.0.0 | 
| Eq1 NonEmpty | Since: base-4.10.0.0 | 
| Ord1 NonEmpty | Since: base-4.10.0.0 | 
| Defined in Data.Functor.Classes | |
| Read1 NonEmpty | Since: base-4.10.0.0 | 
| Defined in Data.Functor.Classes | |
| Show1 NonEmpty | Since: base-4.10.0.0 | 
| NFData1 NonEmpty | Since: deepseq-1.4.3.0 | 
| Defined in Control.DeepSeq | |
| IsList (NonEmpty a) | Since: base-4.9.0.0 | 
| Eq a => Eq (NonEmpty a) | Since: base-4.9.0.0 | 
| Data a => Data (NonEmpty a) | Since: base-4.9.0.0 | 
| Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonEmpty a -> c (NonEmpty a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonEmpty a) # toConstr :: NonEmpty a -> Constr # dataTypeOf :: NonEmpty a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NonEmpty a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonEmpty a)) # gmapT :: (forall b. Data b => b -> b) -> NonEmpty a -> NonEmpty a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r # gmapQ :: (forall d. Data d => d -> u) -> NonEmpty a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NonEmpty a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) # | |
| Ord a => Ord (NonEmpty a) | Since: base-4.9.0.0 | 
| Read a => Read (NonEmpty a) | Since: base-4.11.0.0 | 
| Show a => Show (NonEmpty a) | Since: base-4.11.0.0 | 
| Generic (NonEmpty a) | |
| Semigroup (NonEmpty a) | Since: base-4.9.0.0 | 
| NFData a => NFData (NonEmpty a) | Since: deepseq-1.4.2.0 | 
| Defined in Control.DeepSeq | |
| Hashable a => Hashable (NonEmpty a) | |
| Defined in Data.Hashable.Class | |
| Generic1 NonEmpty | |
| Each (NonEmpty a) (NonEmpty b) a b | |
| type Rep (NonEmpty a) | Since: base-4.6.0.0 | 
| Defined in GHC.Generics type Rep (NonEmpty a) = D1 (MetaData "NonEmpty" "GHC.Base" "base" False) (C1 (MetaCons ":|" (InfixI LeftAssociative 9) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [a]))) | |
| type Item (NonEmpty a) | |
| type Rep1 NonEmpty | Since: base-4.6.0.0 | 
| Defined in GHC.Generics type Rep1 NonEmpty = D1 (MetaData "NonEmpty" "GHC.Base" "base" False) (C1 (MetaCons ":|" (InfixI LeftAssociative 9) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 []))) | |
Non-empty stream transformations
intersperse :: a -> NonEmpty a -> NonEmpty a #
'intersperse x xs' alternates elements of the list with copies of x.
intersperse 0 (1 :| [2,3]) == 1 :| [0,2,0,3]
Basic functions
uncons :: NonEmpty a -> (a, Maybe (NonEmpty a)) #
uncons produces the first element of the stream, and a stream of the
 remaining elements, if any.
inits :: Foldable f => f a -> NonEmpty [a] #
The inits function takes a stream xs and returns all the
 finite prefixes of xs.
tails :: Foldable f => f a -> NonEmpty [a] #
The tails function takes a stream xs and returns all the
 suffixes of xs.
Building streams
iterate :: (a -> a) -> a -> NonEmpty a #
iterate f xf to x.
iterate f x = x :| [f x, f (f x), ..]
cycle :: NonEmpty a -> NonEmpty a #
cycle xsxs:
cycle (1 :| [2,3]) = 1 :| [2,3,1,2,3,...]
insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a #
insert x xsx into the last position in xs where it
 is still less than or equal to the next element. In particular, if the
 list is sorted beforehand, the result will also be sorted.
some1 :: Alternative f => f a -> f (NonEmpty a) #
some1 xx one or more times.
Extracting sublists
drop :: Int -> NonEmpty a -> [a] #
drop n xsn elements off the front of
 the sequence xs.
splitAt :: Int -> NonEmpty a -> ([a], [a]) #
splitAt n xsxs
 of length n and the remaining stream immediately following this prefix.
'splitAt' n xs == ('take' n xs, 'drop' n xs)
xs == ys ++ zs where (ys, zs) = 'splitAt' n xstakeWhile :: (a -> Bool) -> NonEmpty a -> [a] #
takeWhile p xsxs for which the predicate p holds.
span :: (a -> Bool) -> NonEmpty a -> ([a], [a]) #
span p xsxs that satisfies
 p, together with the remainder of the stream.
'span' p xs == ('takeWhile' p xs, 'dropWhile' p xs)
xs == ys ++ zs where (ys, zs) = 'span' p xsfilter :: (a -> Bool) -> NonEmpty a -> [a] #
filter p xsxs that do not satisfy p.
partition :: (a -> Bool) -> NonEmpty a -> ([a], [a]) #
The partition function takes a predicate p and a stream
 xs, and returns a pair of lists. The first list corresponds to the
 elements of xs for which p holds; the second corresponds to the
 elements of xs for which p does not hold.
'partition' p xs = ('filter' p xs, 'filter' (not . p) xs)group :: (Foldable f, Eq a) => f a -> [NonEmpty a] #
The group function takes a stream and returns a list of
 streams such that flattening the resulting list is equal to the
 argument.  Moreover, each stream in the resulting list
 contains only equal elements.  For example, in list notation:
'group' $ 'cycle' "Mississippi" = "M" : "i" : "ss" : "i" : "ss" : "i" : "pp" : "i" : "M" : "i" : ...
groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a] #
groupAllWith operates like groupWith, but sorts the list
 first so that each equivalence class has, at most, one list in the
 output
groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) #
groupWith1 is to group1 as groupWith is to group
groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) #
groupAllWith1 is to groupWith1 as groupAllWith is to groupWith
Sublist predicates
isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool #
The isPrefix function returns True if the first argument is
 a prefix of the second.
Set-like operations
Zipping and unzipping streams
zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) #
The zip function takes two streams and returns a stream of
 corresponding pairs.