listsafe-0.1.0.0: Safe wrappers for partial list functions, supporting MonadThrow.

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.List.Safe

Contents

Description

Operations on lists. This module re-exports all safe functions of List, but wraps all partial functions which may fail. As such, this module can be imported instead of Data.List.

Partial functions are wrapped into the MonadThrow-monad from Control.Monad.Catch and as such, have appropriate failure cases for all instances. E.g.:

  • Nothing for Maybe,
  • the empty list for '[a]',
  • IOException for IO,
  • lifted exceptions for monad transformers.

Synopsis

Safe versions of standard functions.

head :: MonadThrow m => [a] -> m a Source

Extract the first element of a list. Empty lists throw an EmptyListException.

last :: MonadThrow m => [a] -> m a Source

Extract the last element of a list. Empty lists throw an EmptyListException.

tail :: MonadThrow m => [a] -> m [a] Source

Extract the elements after the head of a list. Empty lists throw an EmptyListException.

init :: MonadThrow m => [a] -> m [a] Source

Return all the elements of a list except the last one. Empty lists throw an EmptyListException.

foldl1 :: MonadThrow m => (a -> a -> a) -> [a] -> m a Source

foldl1 is a variant of foldl that has no starting value, and thus must be applied to non-empty lists. Empty lists throw an EmptyListException.

foldl1' :: MonadThrow m => (a -> a -> a) -> [a] -> m a Source

A strict version of foldl1.

foldr1 :: MonadThrow m => (a -> a -> a) -> [a] -> m a Source

foldr1 is a variant of foldr that has no starting value, and thus must be applied to non-empty lists. Empty lists throw an EmptyListException.

maximum :: (MonadThrow m, Ord a) => [a] -> m a Source

maximum returns the maximum value from a list, which must be non-empty, finite, and of an ordered type. It is a special case of maximumBy, which allows the programmer to supply their own comparison function. Empty lists throw an EmptyListException.

minimum :: (MonadThrow m, Ord a) => [a] -> m a Source

minimum returns the maximum value from a list, which must be non-empty, finite, and of an ordered type. It is a special case of minimumBy, which allows the programmer to supply their own comparison function. Empty lists throw an EmptyListException.

maximumBy :: MonadThrow m => (a -> a -> Ordering) -> [a] -> m a Source

The maximumBy function takes a comparison function and a list and returns the greatest element of the list by the comparison function. The list must be finite and non-empty. Empty lists throw an EmptyListException.

minimumBy :: MonadThrow m => (a -> a -> Ordering) -> [a] -> m a Source

The minimumBy function takes a comparison function and a list and returns the least element of the list by the comparison function. The list must be finite and non-empty. Empty lists throw an EmptyListException.

(!!) :: (MonadThrow m, Integral n, Num n) => [a] -> n -> m a Source

List index (subscript) operator, starting from 0. Indices larger than length xs - 1 throw an EmptyListException, negative indices throw an NegativeIndexException.

Generic wrapper for partial functions.

wrap :: MonadThrow m => ([a] -> b) -> [a] -> m b Source

Takes a function that requires a non-empty list and wraps it in an instance of MonadThrow. For empty lists, an EmptyListException is thrown.

Exceptions for empty lists and negative indices.

These are the only two exceptions that will be thrown.

data EmptyListException Source

Signals that the list was empty or contained too few elements (in the case or access by index).

Constructors

EmptyListException