nonempty-wrapper-0.1.0.0: Create NonEmpty version of any container
CopyrightGautier DI FOLCO
LicenseBSD2
MaintainerGautier DI FOLCO <gautier.difolco@gmail.com>
StabilityUnstable
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Data.NonEmpty

Description

Create NonEmpty version of any container.

Synopsis

Base type

data NonEmpty a Source #

NonEmpty proofed value.

Instances

Instances details
Eq a => Eq (NonEmpty a) Source # 
Instance details

Defined in Data.NonEmpty

Methods

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

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

Ord a => Ord (NonEmpty a) Source # 
Instance details

Defined in Data.NonEmpty

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 #

Show a => Show (NonEmpty a) Source # 
Instance details

Defined in Data.NonEmpty

Methods

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

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Semigroup a => Semigroup (NonEmpty a) Source # 
Instance details

Defined in Data.NonEmpty

Methods

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

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

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

$sel:getNonEmpty:NonEmpty :: NonEmpty a -> a Source #

Extract the NonEmpty proven value

trustedNonEmpty :: a -> NonEmpty a Source #

Trusted value

Singleton constructor

class NonEmptySingleton a where Source #

Singleton constructible value

Associated Types

type NonEmptySingletonElement a :: Type Source #

Instances

Instances details
Applicative f => NonEmptySingleton (f a) Source # 
Instance details

Defined in Data.NonEmpty

Associated Types

type NonEmptySingletonElement (f a) Source #

Methods

nonEmptySingleton :: Proxy (f a) -> NonEmptySingletonElement (f a) -> f a Source #

singleton :: NonEmptySingleton a => Proxy a -> NonEmptySingletonElement a -> NonEmpty a Source #

Build a NonEmpty value from a singleton value

newtype MkNonEmptySingletonApplicative a Source #

Build NonEmptySingleton for Applicative defined types to be used with DerivingVia:

deriving instance NonEmptySingleton [a] via (MkNonEmptySingletonApplicative [a])

From container

class NonEmptyFromContainer a where Source #

Used to attempt conversion from possibly empty to NonEmpty.

Methods

isNonEmpty :: a -> Bool Source #

Instances

Instances details
Foldable f => NonEmptyFromContainer (f a) Source # 
Instance details

Defined in Data.NonEmpty

Methods

isNonEmpty :: f a -> Bool Source #

newtype MkNonEmptyFromContainerFoldable a Source #

Build MkNonEmptyFromContainerFoldable for Foldable defined types to be used with DerivingVia:

deriving instance NonEmptyFromContainer [a] via (MkNonEmptyFromContainerFoldable [a])

Operations

(<|) :: Semigroup a => NonEmpty a -> a -> NonEmpty a infixr 6 Source #

Append empty container

(|>) :: Semigroup a => a -> NonEmpty a -> NonEmpty a infixr 6 Source #

Prepend empty container

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

Wrap and unwrap NonEmpty (unsafe, be sure f is size-conservative)

overNonEmpty2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c Source #

Wrap and unwrap NonEmpty (unsafe, be sure f is size-conservative)

overNonEmpty3 :: (a -> b -> c -> d) -> NonEmpty a -> NonEmpty b -> NonEmpty c -> NonEmpty d Source #

Wrap and unwrap NonEmpty (unsafe, be sure f is size-conservative)

overNonEmpty4 :: (a -> b -> c -> d -> e) -> NonEmpty a -> NonEmpty b -> NonEmpty c -> NonEmpty d -> NonEmpty e Source #

Wrap and unwrap NonEmpty (unsafe, be sure f is size-conservative)

overNonEmpty5 :: (a -> b -> c -> d -> e -> f) -> NonEmpty a -> NonEmpty b -> NonEmpty c -> NonEmpty d -> NonEmpty e -> NonEmpty f Source #

Wrap and unwrap NonEmpty (unsafe, be sure f is size-conservative)

fmapNonEmpty :: Functor f => (a -> b) -> NonEmpty (f a) -> NonEmpty (f b) Source #

fmap over a NonEmpty container

withNonEmpty :: (a -> Maybe b) -> NonEmpty a -> b Source #

Apply an unsafe function over empty, which is safe over NonEmpty