relude-1.1.0.0: Safe, performant, user-friendly and lightweight Haskell Standard Library
Copyright(c) 2016 Stephen Diehl
(c) 2016-2018 Serokell
(c) 2018-2022 Kowainik
LicenseMIT
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellSafe
LanguageHaskell2010

Relude.List.NonEmpty

Description

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.

baserelude
head[a] -> aNonEmpty a -> a
tail[a] -> [a]NonEmpty a -> [a]
last[a] -> aNonEmpty a -> a
init[a] -> [a]NonEmpty 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
reludeNonEmpty a -> a
Example with list base> head [1..5]
1
Example with empty list base> head []
*** Exception: Prelude.head: empty list
Example with NonEmpty relude> head $ 1 :| [2..5]
1
Example with list relude> viaNonEmpty head [1..5]
Just 1
Example with empty list relude> viaNonEmpty head []
Nothing

Since: 0.2.0

Synopsis

Reexports from DataList.NonEmpty

data NonEmpty a #

Non-empty (and non-strict) list type.

Since: base-4.9.0.0

Constructors

a :| [a] infixr 5 

Instances

Instances details
Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

Functor NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b #

(<$) :: a -> NonEmpty b -> NonEmpty a #

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

liftA2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Foldable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

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 #

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

elem :: Eq a => a -> NonEmpty a -> Bool #

maximum :: Ord a => NonEmpty a -> a #

minimum :: Ord a => NonEmpty a -> a #

sum :: Num a => NonEmpty a -> a #

product :: Num a => NonEmpty a -> a #

Traversable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) #

Eq1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool #

Ord1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering #

Read1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NonEmpty a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NonEmpty a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NonEmpty a] #

Show1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS #

NFData1 NonEmpty

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> NonEmpty a -> () #

Hashable1 NonEmpty

Since: hashable-1.3.1.0

Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NonEmpty a -> Int #

Foldable1 NonEmpty Source #

Since: 0.3.0

Instance details

Defined in Relude.Extra.Foldable1

Methods

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

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: NonEmpty a -> Q Exp #

liftTyped :: NonEmpty a -> Q (TExp (NonEmpty a)) #

IsList (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item (NonEmpty a) #

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

Eq a => Eq (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(==) :: NonEmpty a -> NonEmpty a -> Bool #

(/=) :: NonEmpty a -> NonEmpty a -> Bool #

Data a => Data (NonEmpty a)

Since: base-4.9.0.0

Instance details

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 :: 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

Instance details

Defined in GHC.Base

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

(<) :: NonEmpty a -> NonEmpty a -> Bool #

(<=) :: NonEmpty a -> NonEmpty a -> Bool #

(>) :: NonEmpty a -> NonEmpty a -> Bool #

(>=) :: NonEmpty a -> NonEmpty a -> Bool #

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

Read a => Read (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Read

Show a => Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Generic (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

NFData a => NFData (NonEmpty a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: NonEmpty a -> () #

Hashable a => Hashable (NonEmpty a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> NonEmpty a -> Int #

hash :: NonEmpty a -> Int #

One (NonEmpty a) Source #

Allows to create singleton NonEmpty list. You might prefer function with name one instead of pure or (:|[]).

>>> one 42 :: NonEmpty Int
42 :| []
law> length (one @(NonEmpty a) x) ≡ 1
Instance details

Defined in Relude.Container.One

Associated Types

type OneItem (NonEmpty a) Source #

Methods

one :: OneItem (NonEmpty a) -> NonEmpty a Source #

Generic1 NonEmpty

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 NonEmpty :: k -> Type #

Methods

from1 :: forall (a :: k). NonEmpty a -> Rep1 NonEmpty a #

to1 :: forall (a :: k). Rep1 NonEmpty a -> NonEmpty a #

type Rep (NonEmpty a) 
Instance details

Defined in GHC.Generics

type Item (NonEmpty a) 
Instance details

Defined in GHC.Exts

type Item (NonEmpty a) = a
type OneItem (NonEmpty a) Source # 
Instance details

Defined in Relude.Container.One

type OneItem (NonEmpty a) = a
type Rep1 NonEmpty 
Instance details

Defined in GHC.Generics

nonEmpty :: [a] -> Maybe (NonEmpty a) #

nonEmpty efficiently turns a normal list into a NonEmpty stream, producing Nothing if the input is empty.

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.