nonempty-lift-0.1: nonempty structure

Safe HaskellSafe
LanguageHaskell2010

NonEmpty

Description

This module provides a way to lift potentially empty structures into one which is guaranteed to be NonEmpty by construction.

Synopsis

Documentation

data NonEmpty f a Source #

A structure which is nonempty by construction.

Typically this will be used to construct list-like structures; e.g.

  • NonEmpty [] a is a lazy list containing at least one element.
  • NonEmpty (NonEmpty []) a is a lazy list containing at least two elements.
  • NonEmpty Maybe a is a list that contains one or two elements.

Constructors

NonEmpty a (f a) 
Instances
ComonadHoist NonEmpty Source # 
Instance details

Defined in NonEmpty

Methods

cohoist :: (Comonad w, Comonad v) => (forall x. w x -> v x) -> NonEmpty w a -> NonEmpty v a #

Functor f => Functor (NonEmpty f) Source # 
Instance details

Defined in NonEmpty

Methods

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

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

Applicative f => Applicative (NonEmpty f) Source # 
Instance details

Defined in NonEmpty

Methods

pure :: a -> NonEmpty f a #

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

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

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

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

Foldable f => Foldable (NonEmpty f) Source # 
Instance details

Defined in NonEmpty

Methods

fold :: Monoid m => NonEmpty f m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmpty f a -> m #

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

foldr' :: (a -> b -> b) -> b -> NonEmpty f a -> b #

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

foldl' :: (b -> a -> b) -> b -> NonEmpty f a -> b #

foldr1 :: (a -> a -> a) -> NonEmpty f a -> a #

foldl1 :: (a -> a -> a) -> NonEmpty f a -> a #

toList :: NonEmpty f a -> [a] #

null :: NonEmpty f a -> Bool #

length :: NonEmpty f a -> Int #

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

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

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

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

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

Traversable f => Traversable (NonEmpty f) Source # 
Instance details

Defined in NonEmpty

Methods

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

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

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

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

(Applicative f, Comonad f) => Comonad (NonEmpty f) Source # 
Instance details

Defined in NonEmpty

Methods

extract :: NonEmpty f a -> a #

duplicate :: NonEmpty f a -> NonEmpty f (NonEmpty f a) #

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

(Comonad f, Applicative f) => ComonadApply (NonEmpty f) Source # 
Instance details

Defined in NonEmpty

Methods

(<@>) :: NonEmpty f (a -> b) -> NonEmpty f a -> NonEmpty f b #

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

(<@) :: NonEmpty f a -> NonEmpty f b -> NonEmpty f a #

Foldable f => Foldable1 (NonEmpty f) Source # 
Instance details

Defined in NonEmpty

Methods

fold1 :: Semigroup m => NonEmpty f m -> m #

foldMap1 :: Semigroup m => (a -> m) -> NonEmpty f a -> m #

toNonEmpty :: NonEmpty f a -> NonEmpty0 a #

Apply f => Apply (NonEmpty f) Source # 
Instance details

Defined in NonEmpty

Methods

(<.>) :: NonEmpty f (a -> b) -> NonEmpty f a -> NonEmpty f b #

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

(<.) :: NonEmpty f a -> NonEmpty f b -> NonEmpty f a #

liftF2 :: (a -> b -> c) -> NonEmpty f a -> NonEmpty f b -> NonEmpty f c #

Generic1 (NonEmpty f :: Type -> Type) Source # 
Instance details

Defined in NonEmpty

Associated Types

type Rep1 (NonEmpty f) :: k -> Type #

Methods

from1 :: NonEmpty f a -> Rep1 (NonEmpty f) a #

to1 :: Rep1 (NonEmpty f) a -> NonEmpty f a #

(Eq a, Eq (f a)) => Eq (NonEmpty f a) Source # 
Instance details

Defined in NonEmpty

Methods

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

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

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

Defined in NonEmpty

Methods

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

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

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

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

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

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

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

(Read a, Read (f a)) => Read (NonEmpty f a) Source # 
Instance details

Defined in NonEmpty

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

Defined in NonEmpty

Methods

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

show :: NonEmpty f a -> String #

showList :: [NonEmpty f a] -> ShowS #

Generic (NonEmpty f a) Source # 
Instance details

Defined in NonEmpty

Associated Types

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

Methods

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

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

type Rep1 (NonEmpty f :: Type -> Type) Source # 
Instance details

Defined in NonEmpty

type Rep1 (NonEmpty f :: Type -> Type) = D1 (MetaData "NonEmpty" "NonEmpty" "nonempty-lift-0.1-LolRZTbfYPLBGQ70KWXXRL" False) (C1 (MetaCons "NonEmpty" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)))
type Rep (NonEmpty f a) Source # 
Instance details

Defined in NonEmpty

type Rep (NonEmpty f a) = D1 (MetaData "NonEmpty" "NonEmpty" "nonempty-lift-0.1-LolRZTbfYPLBGQ70KWXXRL" False) (C1 (MetaCons "NonEmpty" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))

head :: NonEmpty f a -> a Source #

Get the head of a NonEmpty.

tail :: NonEmpty f a -> f a Source #

Get the tail of a NonEmpty.

toList :: Foldable f => NonEmpty f a -> [a] Source #

Convert a NonEmpty into a list.

zip :: MonadZip f => NonEmpty f a -> NonEmpty f b -> NonEmpty f (a, b) Source #

Zip two NonEmptys together.

zipWith :: MonadZip f => (a -> b -> c) -> NonEmpty f a -> NonEmpty f b -> NonEmpty f c Source #

Zip two NonEmptys together with a combining function.

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

Unzip a NonEmpty.

nonEmpty :: a -> f a -> NonEmpty f a Source #

Construct a NonEmpty.