Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2021 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This module contains reexports from Data.List.NonEmpty and safe functions to
work with list type in terms of NonEmpty
.
Note, that Relude reexports head
, tail
, init
, last
from
Data.List.NonEmpty instead of the Data.List, so these functions are safe to
use.
base | relude | |
---|---|---|
head | [a] -> a |
|
tail | [a] -> [a] |
|
last | [a] -> a |
|
init | [a] -> [a] |
|
relude
also provides custom type error for better experience with transition
from lists to NonEmpty
with those functions.
Let's examine the behaviour of the relude
list functions comparing to the
corresponding base
one on the example of the head
function:
head | |
---|---|
base | [a] -> a |
relude |
|
Example
with list
base | > |
1 | |
Example
with empty list
base | > |
*** Exception: Prelude.head: empty list | |
Example
with NonEmpty
relude | > |
1 | |
Example
with list
relude | > |
| |
Example
with empty list
relude | > |
|
Since: 0.2.0
Synopsis
- data NonEmpty a = a :| [a]
- nonEmpty :: [a] -> Maybe (NonEmpty a)
- head :: IsNonEmpty f a a "head" => f a -> a
- tail :: IsNonEmpty f a [a] "tail" => f a -> [a]
- last :: IsNonEmpty f a a "last" => f a -> a
- init :: IsNonEmpty f a [a] "init" => f a -> [a]
- viaNonEmpty :: (NonEmpty a -> b) -> [a] -> Maybe b
- whenNotNull :: Applicative f => [a] -> (NonEmpty a -> f ()) -> f ()
- whenNotNullM :: Monad m => m [a] -> (NonEmpty a -> m ()) -> m ()
Reexports from DataList.NonEmpty
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
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 fold :: Monoid m => NonEmpty m -> m # foldMap :: Monoid m => (a -> m) -> NonEmpty a -> 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 | |
Hashable1 NonEmpty | Since: hashable-1.3.1.0 |
Defined in Data.Hashable.Class | |
Foldable1 NonEmpty Source # | Since: 0.3.0 |
Defined in Relude.Extra.Foldable1 foldMap1 :: Semigroup m => (a -> m) -> NonEmpty a -> m Source # fold1 :: Semigroup m => NonEmpty m -> m Source # foldr1 :: (a -> b -> b) -> b -> NonEmpty a -> b Source # toNonEmpty :: NonEmpty a -> NonEmpty a Source # head1 :: NonEmpty a -> a Source # last1 :: NonEmpty a -> a Source # maximum1 :: Ord a => NonEmpty a -> a Source # minimum1 :: Ord a => NonEmpty a -> a Source # maximumOn1 :: Ord b => (a -> b) -> NonEmpty a -> a Source # minimumOn1 :: Ord b => (a -> b) -> NonEmpty a -> a Source # | |
Lift a => Lift (NonEmpty a :: Type) | Since: template-haskell-2.15.0.0 |
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 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 :: forall r r'. (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) | Since: base-4.6.0.0 |
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 | |
One (NonEmpty a) Source # | Allows to create singleton
law> |
Generic1 NonEmpty | Since: base-4.6.0.0 |
type Rep (NonEmpty a) | |
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 OneItem (NonEmpty a) Source # | |
Defined in Relude.Container.One | |
type Rep1 NonEmpty | |
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 []))) |
head :: IsNonEmpty f a a "head" => f a -> a Source #
O(1)
. Extracts the first element of a NonEmpty
list.
Actual type of this function is the following:
head :: NonEmpty
a -> a
but it was given a more complex type to provide friendlier compile time errors.
>>>
head ('a' :| "bcde")
'a'>>>
head [0..5 :: Int]
... ... 'head' works with 'NonEmpty', not ordinary lists. Possible fix: Replace: [Int] With: NonEmpty Int ... However, you can use 'head' with the ordinary lists. Apply 'viaNonEmpty' function from relude: viaNonEmpty head (yourList) Note, that this will return 'Maybe Int' therefore it is a safe function unlike 'head' from the standard Prelude ...>>>
head (Just 'a')
... ... 'head' works with 'NonEmpty Char' lists But given: Maybe Char ...
tail :: IsNonEmpty f a [a] "tail" => f a -> [a] Source #
O(1)
. Return all the elements of a NonEmpty
list after the head
element.
Actual type of this function is the following:
tail :: NonEmpty
a -> [a]
but it was given a more complex type to provide friendlier compile time errors.
>>>
tail ('a' :| "bcde")
"bcde">>>
tail [0..5 :: Int]
... ... 'tail' works with 'NonEmpty', not ordinary lists. Possible fix: Replace: [Int] With: NonEmpty Int ... However, you can use 'tail' with the ordinary lists. Apply 'viaNonEmpty' function from relude: viaNonEmpty tail (yourList) Note, that this will return 'Maybe [Int]' therefore it is a safe function unlike 'tail' from the standard Prelude ...>>>
tail (Just 'a')
... ... 'tail' works with 'NonEmpty Char' lists But given: Maybe Char ...
last :: IsNonEmpty f a a "last" => f a -> a Source #
O(n)
. Extracts the last element of a NonEmpty
list.
Actual type of this function is the following:
last :: NonEmpty
a -> a
but it was given a more complex type to provide friendlier compile time errors.
>>>
last ('a' :| "bcde")
'e'>>>
last [0..5 :: Int]
... ... 'last' works with 'NonEmpty', not ordinary lists. Possible fix: Replace: [Int] With: NonEmpty Int ... However, you can use 'last' with the ordinary lists. Apply 'viaNonEmpty' function from relude: viaNonEmpty last (yourList) Note, that this will return 'Maybe Int' therefore it is a safe function unlike 'last' from the standard Prelude ...>>>
last (Just 'a')
... ... 'last' works with 'NonEmpty Char' lists But given: Maybe Char ...
init :: IsNonEmpty f a [a] "init" => f a -> [a] Source #
O(n)
. Return all the elements of a NonEmpty
list except the last one
element.
Actual type of this function is the following:
init :: NonEmpty
a -> [a]
but it was given a more complex type to provide friendlier compile time errors.
>>>
init ('a' :| "bcde")
"abcd">>>
init [0..5 :: Int]
... ... 'init' works with 'NonEmpty', not ordinary lists. Possible fix: Replace: [Int] With: NonEmpty Int ... However, you can use 'init' with the ordinary lists. Apply 'viaNonEmpty' function from relude: viaNonEmpty init (yourList) Note, that this will return 'Maybe [Int]' therefore it is a safe function unlike 'init' from the standard Prelude ...>>>
init (Just 'a')
... ... 'init' works with 'NonEmpty Char' lists But given: Maybe Char ...
Combinators
viaNonEmpty :: (NonEmpty a -> b) -> [a] -> Maybe b Source #
For safe work with lists using functions for NonEmpty
.
>>>
viaNonEmpty head [1]
Just 1>>>
viaNonEmpty head []
Nothing
Since: 0.1.0
whenNotNull :: Applicative f => [a] -> (NonEmpty a -> f ()) -> f () Source #
Performs given action over NonEmpty
list if given list is non empty.
>>>
whenNotNull [] $ \(b :| _) -> print (not b)
>>>
whenNotNull [False,True] $ \(b :| _) -> print (not b)
True
whenNotNullM :: Monad m => m [a] -> (NonEmpty a -> m ()) -> m () Source #
Monadic version of whenNotNull
.