zm-0.3.2: Language independent, reproducible, absolute types

Safe HaskellNone
LanguageHaskell2010

ZM.Type.NonEmptyList

Synopsis

Documentation

data NonEmptyList a Source #

A list that contains at least one element

Constructors

Elem a 
Cons a (NonEmptyList a) 

Instances

Functor NonEmptyList Source # 

Methods

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

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

Foldable NonEmptyList Source # 

Methods

fold :: Monoid m => NonEmptyList m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmptyList a -> m #

foldr :: (a -> b -> b) -> b -> NonEmptyList a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmptyList a -> b #

foldl :: (b -> a -> b) -> b -> NonEmptyList a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmptyList a -> b #

foldr1 :: (a -> a -> a) -> NonEmptyList a -> a #

foldl1 :: (a -> a -> a) -> NonEmptyList a -> a #

toList :: NonEmptyList a -> [a] #

null :: NonEmptyList a -> Bool #

length :: NonEmptyList a -> Int #

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

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

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

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

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

Traversable NonEmptyList Source # 

Methods

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

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

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

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

Eq a => Eq (NonEmptyList a) Source # 
Ord a => Ord (NonEmptyList a) Source # 
Show a => Show (NonEmptyList a) Source # 
Generic (NonEmptyList a) Source # 

Associated Types

type Rep (NonEmptyList a) :: * -> * #

Methods

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

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

NFData a => NFData (NonEmptyList a) Source # 

Methods

rnf :: NonEmptyList a -> () #

Flat a => Flat (NonEmptyList a) Source # 
Model a => Model (NonEmptyList a) Source # 
type Rep (NonEmptyList a) Source # 

nonEmptyList :: [a] -> NonEmptyList a Source #

Convert a list to a NonEmptyList, returns an error if the list is empty